Redundant Bang Patterns [GHC-38520]
Flag: -Wredundant-bang-patterns
The BangPatterns
extension allows the user to mark parts of a pattern as strict by prefixing the pattern with an exclamation mark.
By default, Haskell only evaluates an expression as little as it needs to determine whether the pattern matches or not.
Using bang patterns causes the matched expression to always be evaluated to weak head normal
form (WHNF) before the rest of the clauses, any guard patterns, or the right-hand side
of the clause are executed.
However, there are cases where a bang pattern can be redundant.
This happens either because a previous match clause already forced the evaluation, because the user is
trying to match on a strict field of a data type, or because the type of the value being
matched on is of an unlifted or unboxed type like Int#
or Array#
.
In all of these cases, the Bang Pattern has no added effect, so it is redundant.
Examples
Already deconstructed
Warning message
AlreadyDeconstructed.hs:5:15: warning: [-Wredundant-bang-patterns]
Pattern match has redundant bang
In an equation for ‘doubleIfTrue’: doubleIfTrue x = ...
|
5 | doubleIfTrue !x = fst x
| ^
Explanation
It is possible that a previous clause already forced the evaluation of an expression.
For example, doubleIfTrue
’s first clause already deconstructs the pair tuple, so
a bang pattern on the tuple as a whole has no effect in the second clause.
AlreadyDeconstructed.hs
module AlreadyDeconstructed where
doubleIfTrue :: (Int, Bool) -> Int
doubleIfTrue (x, y) | y = x * 2
doubleIfTrue !x = fst x
module AlreadyDeconstructed where
doubleIfTrue :: (Int, Bool) -> Int
doubleIfTrue (x, y) | y = x * 2
doubleIfTrue x = fst x
Strict fields
Warning message
UnliftedTypes.hs:17:6: warning: [-Wredundant-bang-patterns]
Pattern match has redundant bang
In an equation for ‘foo’: foo a = ...
|
17 | foo !a !b !c = ()
| ^
Explanation
Haskell allows a user to annotate fields of a datatype as strict, by prepending their type with an exclamation mark. Pattern matching on such a constructor forces it to WHNF, but this also automatically forces any strict fields to evaluate to WHNF as well. Thus, a Bang Pattern has no effect on a strict field.
StrictField.hs
module StrictField where
data Foo = MkFoo !Int Int
foo :: Foo -> Foo -> ()
foo !a (MkFoo !b !c) = ()
module StrictField where
data Foo = MkFoo !Int Int
foo :: Foo -> Foo -> ()
foo !a (MkFoo b !c) = ()
Unlifted and unboxed types
Warning messages
UnliftedTypes.hs:17:6: warning: [-Wredundant-bang-patterns]
Pattern match has redundant bang
In an equation for ‘foo’: foo a = ...
|
17 | foo !a !b !c = ()
| ^
UnliftedTypes.hs:17:9: warning: [-Wredundant-bang-patterns]
Pattern match has redundant bang
In an equation for ‘foo’: foo b = ...
|
17 | foo !a !b !c = ()
| ^
UnliftedTypes.hs:17:12: warning: [-Wredundant-bang-patterns]
Pattern match has redundant bang
In an equation for ‘foo’: foo c = ...
|
17 | foo !a !b !c = ()
| ^
Explanation
Forcing the evaluation of a value up to WHNF does not make sense for unlifted and unboxed types, because these types can never be represented by an unevaluated expression at runtime. Thus, trying to enforce strictness via a bang pattern has no effect.
UnliftedTypes.hs
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedNewtypes #-}
module UnliftedTypes where
import GHC.Exts
newtype MyInt :: TYPE 'IntRep where
MkMyInt :: Int# -> MyInt
foo :: Int# -> MyInt -> (# Int, Int #) -> ()
foo !a !b !c = ()
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedNewtypes #-}
module UnliftedTypes where
import GHC.Exts
newtype MyInt :: TYPE 'IntRep where
MkMyInt :: Int# -> MyInt
foo :: Int# -> MyInt -> (# Int, Int #) -> ()
foo a b c = ()