Pattern Synonyms, explicitly bi-directional: unnecessary complexity?; intermediate data structures

The Pattern Synonyms paper, section 4.3 ‘Explicitly Bidirectional’ closes by noting the ease of using PattSyns might obscure that they can be computationally demanding. The objective, though, is “we are explicitly providing succinct syntax for arbitrary operations.”

True it is that the syntax for using PattSyns is succinct – indeed it’s a delight. Less succinct, though, is the syntax for declaring PattSyns, especially where you have to make them explicitly bi-directional. That often needs custom ‘ViewPattern’ functions with intermediate data structures. Can we make the decls more direct? Consider the example in that section:

data Point = CP Float Float -- x,y coords
pointPolar :: Point → (Float, Float)
pointPolar (CP x y) = ...
polarPoint :: Float → Float → Point
polarPoint r a = ...
pattern Polar :: Float → Float → Point
pattern Polar r a ← (pointPolar → (r , a))
  where
    Polar r a = polarPoint r a

Because the mapping from Cartesian to Polar format needs arith, that’s met with a couple of conversion functions. Each function must produce a value with two fields for the coords. For polarPoint that’s ok: it’s producing a Point: constructor CP has two fields.

Going the other way, pointPolar would like to produce a Polar with two fields, but that’s a PattSyn not a genuine constructor. So pointPolar produces an ad-hoc pair (r, a) purely for name-binding the fields as args to pseudo-constructor Polar.

It’s unlikely we’ll want to use pointPolar for any other purpose than an intermediary within the PattSyn, because a pair is too type-unsafe of a data structure.

Contrast if the polar coords were a genuine data structure – say as an extra constructor to Point, with a couple of conversion functions:

           | PP Float, Float  -- r, a coords

toCart  (PP r a) = CP (r * cos a) (r * sin a)

toPolar (CP x y) = let r = (sqrt (x ^2 + y ^2)) 
                   in PP r ...                    -- detail omitted

There’s a different way to write those, which puts a name-binding on lhs:

toCart'  (PP r t) | let { x = (r * cos t); y = (r * sin t)} = CP x y

toPolar' (CP x y) | let { r = (sqrt (x ^2 + y ^2)) 
                        ; a = (...)
                        } = PP r a

That style lends itself neatly to an implicitly bi-dir decl, avoiding the ViewPattern, avoiding the intermediary pair, and easier to see what’s going on IMO:

pattern Polar r a | let { x = (r * cos a)
                        ; y = (r * sin a) }
        = CP x y  | let { r = (sqrt (x ^2 + y ^ 2)) 
                        ; a = (...)
                        }
  • Note the let introduces an irrefutable name-binding/“always succeeds” says the Language ref.
  • The free vars must be the same on the two sides of the bi-directional =.
  • The types of those vars must unify name-for-name.
  • Both sides of the = must be syntactically (guarded) patts.
  • It does look weird to see a guard on rhs of =, but these are bidirectional so you need to mentally flip them round when reading from data constructor to pattern.
  • It avoids the ViewPattern invocation with that mystical from nowhere.

Thoughts?

I can see extending this to allow Boolean guards and pattern guards, rather than burying the logic of a partial PattSyn inside the ViewPattern function.

The opening example in the Motivation/Abstraction section of the paper (PattSyns over Seq a datatype, which has lots of gnarly structure inside it) also uses ViewPatterns (two of them) to map to an intermediate data structure (data ViewL a = EmptyL | a :< Seq a), which then maps to the PattSyns. This unnecessary complexity (IMO) is hidden inside Data.Sequence.Internal, so the end user gets their “succinct syntax”.

1 Like

One of the unhelpful effects of using ViewPattern functions, is it’s really hard for a coverage checker to see what’s going on. The use cases for the current ‘Or pattern’ proposal #522 could be met with a PattSyn, but because it wants to cover multiple constructors, they’d have to be buried inside a ViewPattern (or an equivalent inscrutable expression). If PattSyns supported multi-line decls:

data T = T1 String | T2 Int | T3 Int              -- per the proposal

pattern TString :: Maybe String -> T
pattern TString (Just s) <- T1 s
        TString Nothing  <- T2 _
        TString Nothing  <- T3 _

Now when adding an extra constructor T4 String to T, we can also add to an equation to pattern TString. (And for that reason, that pattern is unidirectional.)

A coverage checker can now see TString is total over T – or equally can see coverage at a usage of TString.

2 Likes

Ah, I see I’m reprising a (much) earlier discussion [1997, comparing guards to Wadler’s very early proto-proposal for what became ViewPatterns/PatternSynonyms]. Guards including the let construction released in GHC ~2000, became part of the H2010 Standard.

(“For the price of a one-symbol change in the language syntax we get an upward-compatible change to Haskell that provides a smooth extension of the binding power of pattern matching to guards.” [SPJ]. Haha, as if changing one symbol in the syntax will implement the semantics :wink: )

1 Like

I presume you meant cos a and sin a here?

Oops, thanks well spotted. Corrected.

I like the proposal syntax, though its readability depends too much on your neat alignment. I shudder to think what violence Ormolu would do to it. You should probably create a GHC proposal.

Thanks. I’m first worried whether it could produce the semantics I want. And whether that would fit with how PattSyns are already implemented.

As to readability, PattSyn decls are already a bit weird because you must read the rhs of a bidirectional line as though it’s a pattern, even though (in tricky cases) it looks like an expression. And in particular, the ViewPattern I find too easy to overlook, and with counter-intuitive semantics. (I wish some other way could have been found to achieve that semantics. If ViewPatterns hadn’t already been released, I wonder if PattSyns would have found a better way?)

Yeah, nah, nah. I’m thoroughly dischuffed with writing GHC proposals that just get thrown back in my face. Nobody at GHC high command is interested in making existing features more elegant: they’ve published the academic paper; mere users can just suck up the ugliness.