[GHC] #9891: Fixity declarations for pattern synonyms not persisted
GHC
ghc-devs at haskell.org
Wed Dec 17 03:24:04 UTC 2014
#9891: Fixity declarations for pattern synonyms not persisted
-------------------------------------+-------------------------------------
Reporter: klkblake | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Keywords: | Operating System:
Architecture: Unknown/Multiple | Unknown/Multiple
Difficulty: Unknown | Type of failure: Incorrect
Blocked By: | result at runtime
Related Tickets: | Test Case:
| Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
It appears fixity declarations for pattern synonyms only affect modules
being compiled in the same run as the module the definition is in. For
example, take the following files:
Foo.hs:
{{{#!hs
{-# LANGUAGE PatternSynonyms #-}
module Foo where
data Type = Type Int RawType
data RawType = Product Type Type
| Num
pattern a :*: b <- Type _ (Product a b)
infixr 7 :*:
}}}
Bar.hs:
{{{#!hs
{-# LANGUAGE PatternSynonyms #-}
module Main where
import Foo
value = Type 0 $ Product (Type 1 Num) $ Type 2 $ Product (Type 3 Num) $
Type 4 Num
somethingElse = 23
main = case value of
_ :*: _ :*: _ -> putStrLn "Success"
_ -> putStrLn "Fail"
}}}
On the first compile, the executable will print "Success". Modifying Bar
and recompiling will result in it printing "Fail". Modifying both and
recompiling results in "Success" again.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9891>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list