[GHC] #13646: strict patterns with no bindings (e.g. `let !() = ...`) trigger -Wunused-pattern-binds
GHC
ghc-devs at haskell.org
Thu May 4 20:40:40 UTC 2017
#13646: strict patterns with no bindings (e.g. `let !() = ...`) trigger -Wunused-
pattern-binds
-------------------------------------+-------------------------------------
Reporter: exphp | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
In each of the following programs, a bang pattern is used to force
evaluation of a bottom, the intent being to perform fail-fast error
checking. Unfortunately, however, they also generate `-Wunused-pattern-
binds`.
{{{#!hs
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE BangPatterns #-}
main :: IO ()
main = do
let !Nothing = Just ()
pure ()
}}}
{{{#!hs
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE BangPatterns #-}
import Control.Exception
main :: IO ()
main = do
let !() = assert False ()
pure ()
}}}
{{{
src/Lib.hs:6:9: warning: [-Wunused-pattern-binds]
This pattern-binding binds no variables: !Nothing = Just ()
Linking src/Lib ...
Lib: src/Lib.hs:6:9-26: Irrefutable pattern failed for pattern Nothing
--------------------
src/Lib.hs:8:9: warning: [-Wunused-pattern-binds]
This pattern-binding binds no variables: !() = assert False ()
Linking src/Lib ...
Lib: Assertion failed
CallStack (from HasCallStack):
assert, called at src/Lib.hs:8:15 in main:Main
}}}
For clarity, non-monadic `let ... in` patterns are also affected; I only
gloss over them because there tends to be other equally ergonomic
alternatives in such cases.
I found this #9127 (ticket), where a patch was accepted to allow wildcards
of the form `!_`. However, `!_` is unsatisfactory and perhaps even
dangerous for such usage, as it does not constrain the type in any manner.
In particular, there is nothing to prevent somebody from writing
{{{#!hs
main = do
let !_ = assert someCondition -- (missing an argument)
pure ()
}}}
which //is// in fact useless.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13646>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list