[GHC] #15504: -XStrict doesn't prevent warnings from -Wunbanged-strict-patterns
GHC
ghc-devs at haskell.org
Fri Aug 10 20:55:28 UTC 2018
#15504: -XStrict doesn't prevent warnings from -Wunbanged-strict-patterns
-------------------------------------+-------------------------------------
Reporter: ChaiTRex | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Compiler | Version: 8.4.3
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:
-------------------------------------+-------------------------------------
I'm using:
{{{
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 8.4.3
}}}
I was under the impression that
[https://ghc.haskell.org/trac/ghc/wiki/StrictPragma#Strict -XStrict]
automatically included outermost bang patterns, but either that isn't
always the case or [https://downloads.haskell.org/~ghc/master/users-guide
/using-warnings.html#ghc-flag--Wunbanged-strict-patterns -Wunbanged-
strict-patterns] doesn't know that `-XStrict` did its job correctly:
{{{#!hs
{-# OPTIONS_GHC -Wunbanged-strict-patterns #-}
{-# LANGUAGE BangPatterns, MagicHash, Strict, UnboxedTuples #-}
module Example where
import GHC.Exts (Int(I#), quotRemInt#)
lastDigit :: Int -> Int
lastDigit (I# x) = let (# q, r #) = quotRemInt# x 10#
in I# r
}}}
compiles with a warning:
{{{
[1 of 1] Compiling Example ( Example.hs, Example.o )
Example.hs:9:24: warning: [-Wunbanged-strict-patterns]
Pattern bindings containing unlifted types should use
an outermost bang pattern:
(# q, r #) = quotRemInt# x 10#
|
9 | lastDigit (I# x) = let (# q, r #) = quotRemInt# x 10#
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15504>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list