[GHC] #16339: Cannot put (.) or (!) into an export list
GHC
ghc-devs at haskell.org
Tue Feb 19 14:56:15 UTC 2019
#16339: Cannot put (.) or (!) into an export list
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.7
(Parser) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Thanks to recent work in GHC HEAD, it is now possible to define type
operators named `(.)` and `(!)`:
{{{#!hs
type (f . g) x = f (g x)
type x ! f = f x
}}}
However, I was surprised to discover that it's not possible to put them in
an export list! That is to say, this program doesn't parse:
{{{
{-# LANGUAGE TypeOperators #-}
module Bug (type (.), type (!)) where
type (f . g) x = f (g x)
type x ! f = f x
}}}
{{{
$ ~/Software/ghc4/inplace/bin/ghc-stage2 --interactive Bug.hs
GHCi, version 8.7.20190219: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
Bug.hs:2:19: error: parse error on input ‘.’
|
2 | module Bug (type (.), type (!)) where
| ^
}}}
This problem appears to be specific to the `(.)` and `(!)` type operators,
since any other type operator will work in its place:
{{{#!hs
{-# LANGUAGE TypeOperators #-}
module Works (type (&)) where
type (f & g) x = f (g x)
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16339>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list