Skip to content

Commit

Permalink
Add documentation for GHC-38520 (Redundant Bang Patterns)
Browse files Browse the repository at this point in the history
Fixes #177
  • Loading branch information
Adowrath committed Jun 12, 2024
1 parent f7c49e5 commit 48d3963
Show file tree
Hide file tree
Showing 10 changed files with 156 additions and 0 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module AlreadyDeconstructed where

doubleIfTrue :: (Int, Bool) -> Int
doubleIfTrue (x, y) | y = x * 2
doubleIfTrue x = fst x
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module AlreadyDeconstructed where

doubleIfTrue :: (Int, Bool) -> Int
doubleIfTrue (x, y) | y = x * 2
doubleIfTrue !x = fst x
21 changes: 21 additions & 0 deletions message-index/messages/GHC-38520/alreadyDeconstructed/index.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
---
title: 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 match clause already forced the evaluation of a value,
just to reject it and try later patterns.
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.
22 changes: 22 additions & 0 deletions message-index/messages/GHC-38520/index.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
---
title: Redundant Bang Patterns
summary: Used a Bang Pattern that has no Effect
severity: warning
flag: -Wredundant-bang-patterns
introduced: 9.6.1
---

The `BangPatterns` extension allows the user to mark (parts of) a pattern match as strict,
compared to Haskell's default of only evaluating a pattern match as little as it needs to
to determine whether to reject it or not.
This is done by prefixing the pattern with an exclamation mark, `!`.
Using bang patterns causes such values to always be strictly evaluated to Weak head normal
form (WHNF), before the rest of the matches, any guard patterns or the right-hand side
of a function clause are executed.

However, there are cases where a bang pattern can be redundant.
Either this is because a previous match clause was already stricter, 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.
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
module StrictField where

data Foo = MkFoo !Int Int

foo :: Foo -> Foo -> ()
foo !a (MkFoo b !c) = ()
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
module StrictField where

data Foo = MkFoo !Int Int

foo :: Foo -> Foo -> ()
foo !a (MkFoo !b !c) = ()
22 changes: 22 additions & 0 deletions message-index/messages/GHC-38520/strictField/index.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
---
title: 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.
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
{-# 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 = ()
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
{-# 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 = ()
35 changes: 35 additions & 0 deletions message-index/messages/GHC-38520/unliftedTypes/index.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
---
title: 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 breaks down with unlifted and
unboxed types, which explicitly lack a wrapping thunk (there is no *box*),
and so values of such types are already always strict.
Thus, trying to enforce strictness via a bang pattern has no effect.

0 comments on commit 48d3963

Please sign in to comment.