
#12001: RFC: Add pattern synonyms to base -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: libraries/base | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by Iceland_jack): Some random ideas, === Data.Functor.Const === {{{#!hs pattern K :: forall a (b :: k). a -> Const a b pattern K a = Const a pattern K' :: forall a (b :: k). a -> Constant a b pattern K' a = Constant a }}} === GHC.Generics === {{{#!hs isAssociative :: Associativity -> Bool isAssociative LeftAssociative = True isAssociative RightAssociative = True isAssociative NotAssociative = False pattern Associative :: Associative pattern Associative <- (isAssociative -> True) }}} === Data.Ratio === {{{#!hs pattern Denominator :: a -> Ratio a pattern Denominator a <- (denominator -> a) pattern Numerator :: a -> Ratio a pattern Numerator a <- (numerator -> a) pattern (:%) :: Integral a => a -> a -> Ratio a pattern num :% den <- ((\r -> (numerator r, denominator r)) -> (num, den)) where num :% den = num % den }}} === System.Exit === {{{#!hs exitCode :: ExitCode -> Int exitCode = \case ExitSuccess -> 0 ExitFailure n -> n pattern ExitCode :: Int -> ExitCode pattern ExitCode n <- (exitCode -> n) where ExitCode 0 = ExitSuccess ExitCode n = ExitFailure n }}} === Data.Maybe === {{{#!hs pattern Some :: a -> Maybe a pattern Some a = Just a pattern None :: a -> Maybe a pattern None = Nothing }}} === Data.Functor.Identity === {{{#!hs pattern I :: a -> Identity pattern I a = Identity a }}} === Data.Ord === {{{#!hs pattern :: Ordering pattern Less = LT pattern :: Ordering pattern Equal = EQ pattern :: Ordering pattern Greater = GT }}} === Data.Foldable === {{{#!hs pattern Null :: Foldable f => f a pattern Null <- (null -> True) }}} === Data.Bool === {{{#!hs pattern T :: Bool pattern T = True pattern F :: Bool pattern F = False }}} It's fine if these don't get accepted, just throwing them into the universe -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12001#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler