[GHC] #5144: Pattern synonyms

GHC ghc-devs at haskell.org
Mon Aug 12 14:12:31 CEST 2013


#5144: Pattern synonyms
-------------------------------------+------------------------------------
        Reporter:  simonpj           |            Owner:  cactus
            Type:  feature request   |           Status:  new
        Priority:  normal            |        Milestone:  _|_
       Component:  Compiler          |          Version:
      Resolution:                    |         Keywords:
Operating System:  Unknown/Multiple  |     Architecture:  Unknown/Multiple
 Type of failure:  None/Unknown      |       Difficulty:  Unknown
       Test Case:                    |       Blocked By:
        Blocking:                    |  Related Tickets:
-------------------------------------+------------------------------------

Comment (by cactus):

 Progress update: the following module demonstrates all the features
 implemented so far:

 {{{
 {-# LANGUAGE PatternSynonyms #-}
 module PatSyn where

 -- The example from the wiki page
 data Type = App String [Type] deriving Show
 pattern Arrow t1 t2 = App "->" [t1, t2]
 pattern Int = App "Int" []

 collectArgs :: Type -> [Type]
 collectArgs (Arrow t1 t2) = t1 : collectArgs t2
 collectArgs _ = []

 isInt Int = True
 isInt _ = False

 arrows :: [Type] -> Type -> Type
 arrows = flip $ foldr Arrow

 -- Simple pattern synonyms
 pattern Nil = []
 pattern Cons x xs = x:xs

 zip' :: [a] -> [b] -> [(a, b)]
 zip' (Cons x xs) (Cons y ys) = Cons (x, y) (zip' xs ys)
 zip' Nil         _           = Nil
 zip' _           Nil         = Nil

 pattern One x = [x]

 one :: [a] -> Maybe a
 one (One x) = Just x
 one _ = Nothing

 singleton :: a -> [a]
 singleton x = One x

 -- Pattern only synonyms
 pattern Third x = _:_:x:_

 third :: [a] -> Maybe a
 third (Third x) = Just x
 third _         = Nothing

 -- This causes a type error:
 invalid x = Third x

 -- PatSyn.hs:30:13:
 --     Third used in an expression, but it's a non-bidirectional pattern
 synonym
 --     In the expression: Third x
 --     In an equation for ‛invalid’: invalid x = Third x
 -- Failed, modules loaded: none.
 }}}

 The following module also works, but demonstrates the clunkiness caused by
 the lack of infix pattern synonyms:

 {{{
 {-# LANGUAGE ViewPatterns, PatternSynonyms #-}
 import qualified Data.Sequence as Seq

 pattern Empty = (Seq.viewl -> Seq.EmptyL)
 pattern Cons x xs = (Seq.viewl -> x Seq.:< xs)
 pattern Snoc xs x = (Seq.viewr -> xs Seq.:> x)

 zipZag :: Seq.Seq a -> Seq.Seq b -> Seq.Seq (a, b)
 zipZag (Cons x xs) (Snoc ys y) = (x, y) Seq.<| zipZag xs ys
 zipZag _           _           = Seq.empty
 }}}

 Of course, implementing infix pattern synonyms should be easy.

 Still missing: exporting of pattern synonyms.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/5144#comment:16>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler




More information about the ghc-tickets mailing list