[GHC] #8761: Make pattern synonyms work with Template Haskell
GHC
ghc-devs at haskell.org
Fri Oct 30 20:06:40 UTC 2015
#8761: Make pattern synonyms work with Template Haskell
-------------------------------------+-------------------------------------
Reporter: goldfire | Owner:
Type: feature request | Status: new
Priority: normal | Milestone: 8.0.1
Component: Template Haskell | Version:
Resolution: | Keywords:
| PatternSynonyms
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 sboo):
one motivation is for fixed points
https://www.reddit.com/r/haskell/comments/3qrkzr/one_weird_trick_for_nicer_functor_fixpoints/cwhsy6i
for example:
{{{#!hs
{-# LANGUAGE TemplateHaskell, PatternSynonyms, DeriveFunctor #-}
data TreeF a r
= LitF a
| VarF String
| BinF r Operation r
deriving Functor
data Operation = Add | ...
makeFix ''TreeF
}}}
would generate:
{{{#!hs
type Tree a = Fix (TreeF a)
pattern Lit :: a -> Tree a
pattern Lit a = Fix (LitF a)
pattern Var :: String -> Tree a
pattern Var s = Fix (VarF s)
pattern Bin :: Tree a -> Operation -> Tree a -> Tree a
pattern Bin l op r = Fix (BinF l op r)
}}}
which would make `TreeF` as easy to use as `Tree` when using pattern
matching:
{{{#!hs
optimize :: Tree a -> Tree a
optimize (Bin (Lit x) Add (Lit y)) = Lit (x + y)
optimize ... = ...
}}}
and still as easy when using recursion schemes:
{{{#!hs
evalTreeF :: Map String Integer -> TreeF Integer (Maybe Integer) -> Maybe
Integer
evalTreeF environment (BinF (Just l) Add (Just r)) = Just (l + r)
evalTreeF ...
evalTree :: Map String Integer -> Tree Integer -> Maybe Integer
evalTree environment = cata (evalTreeF environment)
}}}
(sorry if here's the wrong place, this is my first post)
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8761#comment:11>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list