Excellent bikeshedding opportunity! Frontend syntax for pattern synonym types

Dr. ERDI Gergo gergo at erdi.hu
Sun Dec 22 14:09:39 UTC 2013


Hi,

As part of my work to add pattern synonyms to GHC 
(https://ghc.haskell.org/trac/ghc/ticket/5144) I initially planned to 
postpone implementing type signatures 
(https://ghc.haskell.org/trac/ghc/ticket/8584). However, since adding the 
feature in the first place requires Haddock support, some syntax will be 
needed for pattern synonym type signatures so that at least there's 
something to generate into the docs.

The basic problem with pattern synonyms in this regard is that their type 
is fully described by the following five pieces of information:

1, Universially bound type variables
2, Existentially bound type variables
3, The (tau) type itself
4, Typeclass context required by the pattern synonym
5, Typeclass context provided by the pattern synonym

To give you some parallels, functions are described by (1), (3) and (4), 
e.g. given the following definition:

     f = map fromIntegral

(1) is {a, b}
(3) is [a] -> [b]
(4) is (Integral a, Num b)

Data constructors are described by (1), (2), (3) and (5), e.g. given

     data T a where
       MkT :: (Num a, Eq b) => a -> (b, b) -> T a

the type of `MkT` is described by

(1) Universially bound type variables {a}
(2) Existentially bound type variables {b}
(3) Tau type a -> (b, b) -> T a
(5) Typeclass context provided is (Num a, Eq b)

Note that when using `MkT` in an expression, its type is simpler than 
that, since it simply becomes

     forall a b. (Num a, Eq b) => a -> (b, b) -> T a

which has exactly the same shape as the previous example which had (1), 
(3) and (4) specified. However, the context has different semantics 
(and the distinction between (1) and (2) becomes important) when pattern 
matching on `MkT`.

For pattern synonyms, all five axes are present and orthogonal, and all 
five is something that a user should care about. For example, given the 
following code:

     {-# LANGUAGE PatternSynonyms, GADTs, ViewPatterns #-}
     data T a where
 	MkT :: (Num a, Eq b) => a -> b -> T a

     f :: (Show a) => a -> Bool
     f = ...

     pattern P x <- MkT (f -> True) x

to fully describe the type of pattern synonym P, we have:

(1) Universially quantified type variables {a}
(2) Existentially quantified type variables {b}
(3) Tau type b -> T a
(4) Required context (Show a)
(5) Provided context (Num a, Eq b)

So, what I'm looking for, is ideas on what syntax to use to represent 
these five pieces of information.

Note that (1) and (2) can be made implicit, just like for constructor 
types, simply by noting that type variables that don't occur in the result 
type are existentially bound. So the tricky part is maintaining the 
distinction between (4) and (5).

The current implementation displays the following if you ask for `:info 
T`:

     > :info P
     pattern P ::
       b -> T t
       requires (Show t)
       provides (Num t, Eq b)

but I don't think we would want to use that for syntax that is actually 
enterred by the user into type signatures (if nothing else, then simply 
because why would we want to use two extra keywords 'requires' and 
'provides').

The one idea I've had so far is to separate (4), (3) and (5) with 
two double arrows:

     pattern P :: (Show t) => b -> T t => (Num t, Eq b)


As an added extra problem, there are also unidirectional and bidirectional 
pattern synonyms: unidirectional ones are usable only as patterns, whereas 
bidirectional ones can also be used as expressions. For example:

     pattern Single x = [x]
     pattern Second x <- (_:x:_)

in this example, `Single` is bidirectional and `Second` is unidirectional. 
As you can see, this is indicated by syntax in the definition (`=` vs 
`<-`). However, I'd like to show this in the type as well, since you'd 
need to be able to see if you can use a given pattern synonym as a 
"constructor", not just a "destructor", by just looking at its 
Haddock-generated docs.


What do you think?

Bye,
 	Gergo

-- 

   .--= ULLA! =-----------------.
    \     http://gergo.erdi.hu   \
     `---= gergo at erdi.hu =-------'
Either the chocolate in my pocket has melted, or this is something altogether more sinister.


More information about the Glasgow-haskell-users mailing list