[GHC] #12857: associate pattern synonyms with a type synonym
GHC
ghc-devs at haskell.org
Sun Nov 20 11:24:33 UTC 2016
#12857: associate pattern synonyms with a type synonym
-------------------------------------+-------------------------------------
Reporter: int-e | Owner:
Type: feature | Status: new
request |
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
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 believe it would be useful to bundle pattern synonyms with type
synonyms, which is currently not supported. For example, the `State` type
synonym from monad transformers could profit from such bundling, as it
would allow users to use `State (..)` in an import list:
{{{#!hs
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}
module State (
State (State, runState)
) where
import Control.Monad
newtype Identity a = Identity { runIdentity :: a }
newtype StateT s m a = StateT { runStateT :: s -> m (s, a) }
type State s a = StateT s Identity a
pattern State { runState } <- ((runIdentity .) . runStateT -> runState)
where State runState = StateT (Identity . runState)
}}}
(I would have a use for this in `haskell-src-exts-simple` package, which,
similar to the above example, uses type synonyms to instantiate a type
parameter a few datatypes to a fixed type.)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12857>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list