`ViewPatterns`: why does the arrow point the wrong way?

I guess I will never be able to use ViewPatterns correctly on the first attempt.

I am gradually/grudgingly understanding there are places where it seems you have to use ViewPatterns. Haskell has too many ways to write pattern matching/condition checking/variable binding; each has annoying restrictions which mean they’re almost, but not quite, equivalent [**]. Let me start with my award for obfuscated Haskell:

  parsePacket :: ByteString -> ...
  parsePacket (bits 3 -> Just (n, (bits n -> Just (val, bs)))) = ...

From the Wiki page linked from the User Guide. I think that’s equivalent to:

parsePacket _p
            | Just (n,   _vbs) <- bits 3 _p
            , Just (val, bs)   <- bits n _vbs   = ...

(I’ve introduced a couple of extra vars preceded with _ to hold intermediate values.)

I think that’s not only equivalent in terms of delivered result, but also in performance profile: if bits 3 _p returns Nothing, the whole match fails/there’s no attempt to try bits n _vbs. I see in the guards the arrow <- points leftwards just like in List and Monad comprehensions; the ‘target’ of the binding is to the left, just as Haskell has always had it in top-level bindings or local: let (Just (n, _vbs)) = ... in ....

It’s also comforting to see the function bits applied to the correct number of arguments I’d expect from its type.

But there are places in the syntax you can’t replace a ViewPattern call with guards, such as in a lambda-expression:

parsePacket = (\(bits 3 -> Just (n, (bits n -> Just (val, bs)))) -> ...)

But, but! a lambda is exactly the place my eye is expecting a ->, so now I have to squint at all those parens to figure which one ‘belongs to’ the \.

I was hoping I could do away with ViewPatterns and use PatternSynonyms but:

clunky env (lookup env -> Just val1) (lookup env -> Just val2) = val1 + val2

(clunky from the User Guide is the standard example/poster-child for an awkward pattern match – see this bit of ancient history 1997.) ViewPatternistas are claiming they’ve overcome the clunkiness. YMMV. I can’t put a PatternSynonym in place of those ViewPattern calls, because lookup is using the argument env as well as the unnamed second or third arguments to clunky. So this isn’t really a view over a single value.

Also in PatternSynonym definitions, there are places you have to use ViewPatterns.

Questions

  • Why does the arrow point the wrong way? Yes I see the bindings flow one from another. Guards also express that flow with a comma-list without needing to put the binding backwards. What else in Haskell uses -> in a comparable way?
  • Do we really have to hide/make implicit the underlying value? And what if I want a name-binding for that as well as the View?
clunky env (Just val1 <- lookup env v1)@v1 (Just val2 <- lookup env v2)@v2 = val1 + val2
  • Could we introduce guards syntax (comma list) in more pattern positions?, for example:
clunky = (\env v1 v2 | Just val1 <- lookup env v1, Just val2 <- lookup env v2 -> val1 + val2)

(Look ma! no parens.) With the same pattern match fail semantics if the lookups return Nothing.

[**] A bit of history

  • Wadler on Views 1987; Wadler et al specifically for Haskell 1996.
  • SPJ Pattern guards proposal 1997; implemented after Haskell 98; included in H2010 standard.
  • ViewPatterns GHC 6.10 2008/2009
  • PatternSynonyms GHC 7.8~8.2 2014~2017

Those extensions are in the ‘same ball park’/draw on Wadler’s 1980’s ideas/have many overlapping use cases, without exactly matching (hah!) capabilities.

I don’t know if you’re just proposing a novel, more verbose syntax, but it sort of sounds like you’re saying that you can’t bind the original parameters to names when using the existing view pattern syntax, and in case that is what you’re saying, you certainly can:

clunky env v1@(lookup env -> Just val1) v2@(lookup env -> Just val2) = val1 + val2

Does MultiWayIf not do this well enough for you?

clunky = (\env v1 v2 -> if | Just val1 <- lookup env v1, Just val2 <- lookup env v2 -> val1 + val2)

Thanks. Chiefly I was complaining about the invisible last argument to lookup. I’m thinking putting the v1@(... {- notionally v1 goes here -} -> ...) in front of the backwards arrow is not an improvement in readability.

Ah, ok great! That’s a new extension for me. (Why isn’t it doco’d in with the other extensions I’m discussing? Released 7.6 ~2012 [***]. Did I mention there’s too many nearly-equivalent ways to express matching/conditional binding?) So perhaps I’m not forced to use ViewPatterns? (To check: does that work within PatternSynonym decls?)

[***] \case arrived in the same release, which also is a conditional/binding mechanism.

Only in the approximately 25% of the pattern synonym decl that allows arbitrary expressions, I would think. It’s not clear to me what you want it for; I don’t really see this as an alternative to the usual view pattern trick for patsyns but maybe you have a clever notion I’m not thinking of.

I mean usages like this, per my link

data Pair a = a :# a

pattern Pair1 :: Pair a -> (Bool -> a)
pattern Pair1 (a :# a') <- (($ False) &&& ($ True) -> (a, a'))
  where Pair1 (a :# _)  False = a
        Pair1 (_ :# a') True  = a'

--  issue started from

newtype Vec a (n :: Nat) = Vec { unVec :: [a] }

pattern VCons :: a -> Vec a n -> Vec a (n + 1)
pattern VCons x xsV <- Vec (x : (Vec -> xsV)) where
    VCons x (Vec xsL) = Vec (x : xsL)

(That second is annoying/tantalising because the line forced to use -> is transparently just a mangled form of the underneath line. Can’t I write the underneath line as the single bidirectional PattSyn and get GHC to figure out the top line for itself?)

I agree, thank you. the RHS of a PattSyn top line must be a pattern; whereas MultiwayIf is an expression.

The appeal of PattSyns is they can be used both for matching and building, and keep abstract the underlying data decl. The syntax for declaring them (needing ViewPatterns) seems to be aimed at library authors/writing highly abstract code. Whereas I think they could have wider usage to express complex conditions – if only they were easier to declare.

It allows to mix guard and view pattern syntax.

1 Like

Okaaay. (Nobody’s going to like this.)

newtype Vec a (n :: Nat) = Vec { unVec :: [a] }   -- reminder, from above
pattern VCons :: a -> Vec a n -> Vec a (n + 1)    --

pattern VCons x xsV           <- Vec (x : xsL@(const $ Vec xsL -> xsV)) where
        VCons x xsV@(Vec xsL)  = Vec (x : xsL)   
  • Because that’s an explicitly bidir declaration, the free vars each side on the top line don’t have to be the same.
  • The (const $ ... -> ...) in effect says to ignore the implicit arg hidden by the ->.
  • So I can give the function (Vec in this case) an explicit argument.
  • I’m feeling weirded out that the xsL@(...) is binding xsL :: [a]; but the expression pattern it’s binding to is :: Vec a n – or maybe :: [a] -> Vec a n.

Perhaps this is an argument (hah!) for an alternative form of ViewPattern with arrow the other way round:

pattern VCons x xsV           <- Vec (x : xsL@(xsV <- Vec xsL)) where ...

               -- or even

pattern VCons x xsV@(Vec xsL)  = Vec (x : xsL@(xsV <- Vec xsL)) 
               -- ^^ @s-pattern not currently allowed on LHS
                           -- ^^ free vars now same both sides, can be bidir

I think hiding the underlying value is the point of ViewPattern. If you need the name of the original value then standard guard syntax is just fine.

clunkyGuard env v1 v2 | Just val1 <- lookup env v1, Just val2 <- lookup env v2 = val1 + val2

I am not sure there are major benefits in using having the guard within the argument as you suggest, vs the actual guards syntax. The only benefit would be for lambda expressions. However that will encourage partial lambdas which I’m not sure is a good idea.

Hiding the value has two benefits, it means you can forbid the initial value to be used (and stop yourself to shoot yourself in the foot as in), compare

compareLower (toLower -> a) (toLower -> b) = a == b

with

compareLower2  a b = (toLower a) == (toLower b)

And you don’t have to waste brain power to name something you don’t want people to use.
Even though I agree that the arrow point in the wrong way, reversing it would be extremely confusing.
So far, x <- v appears in many places (guards, do block, list comprehension) but is alway consistent, v contains or product 0 or more xs.
with PatternView f -> x, f is not value but a function to be applied on a hidden parameter. Reversing it would mean that y in x <- y would have different a kind(?) depending on it’s placement.

3 Likes

lambdas with ViewPatterns embedded are partial. The semantics of the application is that lookup might fail but you’re not going to catch it (with a \case for example).

Sure. And a better way to achieve those benefits is via PatternSynonyms IMO.

compareLower (ToLower a) (ToLower b) = a == b

But AFAICT I still need ViewPatterns in the definition for PattSyns.

That’s a matter of taste, I personnaly use PatternSynonyms to validate (IsLower for example) or destructure but not to transfrom a value.

1 Like

This is all a matter of taste indeed. There’s another perspective I sometimes use when thinking about view patterns, instead of ‘there’s a hidden argument to which the view pattern function gets applied’.

It’s customary to think about functions as transforming values (the input) to other values (the output). But it’s equally valid in most contexts to think about functions as transforming a place-to-put-values (the output) into another place-to-put-values (the input). This is the core insight of the CPS transformation, but you don’t have to actually transform your code into CPS to think this way.

Just as a term is the Haskell-source representation of a value, a pattern is (imperfectly, because we have much better tools for composing and abstracting over terms than patterns in Haskell) the Haskell-source representation of a place-to-put-values. We construct terms by applying constructors that map the entire domain to some subset of the codomain. Likewise, we construct patterns by applying constructors that map the entire domain of places-to-put-values (the inner pattern) into a subset of the codomain of places-to-put-values (the possibly-fallible outer pattern).

But we also have functions, not only constructors. Among terms, functions are also maps from (assuming totality) an entire domain of values to a subset (possibly the entire set) of the codomain of values. But from the place-to-put-values perspective, a function maps a subset of the places-to-put-values for its codomain to the entire set of places-to-put-values for its domain. That means that in this perspective, a function is applied to a fallible pattern to form an infallible pattern. Which is precisely what a view pattern is: a pattern that is always happy to match whatever it is being matched against, and delegates any responsibility for handling failure-to-match to its ‘argument’.

In other words, -> in view patterns is the pattern-ish equivalent of the term-ish $:

  • f $ Just (x :: a) uses a function f :: Maybe a -> b that could apply to the entire domain of Maybe a to return a value in the codomain b, and applies it to the specific value in that domain of Just x.
  • g -> Just (x :: a) uses a function g :: b -> Maybe a that could apply to the entire codomain of places-that-receive-values of type Maybe a to return a place-that-receives-values in the domain b, and applies it to the specific place-that-receives-values in that codomain of Just x.

This is probably a terrible way to explain all of this but the symmetry inspires a lot of affection for view patterns in me.

2 Likes

I’m getting a vibe of Backus’ FP. Which I never liked, precisely because it’s all combining forms, no variables.

Yeah sorry, the explanation didn’t work for me. Nor did it inspire any affection for ViewPatterns. In particular, I think the whole point about ViewPatterns is they’re not symmetric – as opposed to PattSyns.

A couple of historical perspectives:

  • In Wadler’s original papers/memos on Views, there’s a clear idea they’re just a different way of processing the one data structure – for example snoc lists vs. cons lists. So this is the same idea as PatternSynonyms: the synonym is of the same type as the underlying data constructor; can be used to both match (consume) and build (produce) a value. PattSyns are ideally bijections.
  • The ViewPattern way (if you look at the ‘futures’ material that didn’t get implemented, and then PattSyns came along) is that the two structure are not same type/not isomorphic. There’s a suggestion the -> is like the function arrow, and denotes a morphism method view:
class View a b where { view :: a -> b }

The morphing might fail; so every reason there’d be instance View a (Maybe b). I don’t see any sense in a morphism Maybe b -> a: if you’ve successfully got Just b, your morphism is b -> Maybe a. Not symmetrical.

If you intend your view is a bijection, that needs both instance View a b and instance View b a. Probably b is a newtype over a but with no guarantee the round trip gives back the same value. So to take the toLower example (I’ve added @s-patterns):

We’d want toLower :: Char -> LChar with newtype LChar = LChar Char; instance View Char LChar; and no reverse instance, because toLower throws away information as to whether the incoming Char was Upper.

There’s no danger of ‘shooting yourself in the foot’ with multiple names in scope, because those names are at different (new)types.

ViewPatterns work only in patterns; there’s no idea you’re going to retrobuild a value of the original type.

Having got a new gizmo, you can’t stop people abusing it: the clunky example is not a morphism over a single value: lookup takes two arguments, it’s a morphism on some value in context of some env.

Neither are PattSyns necessarily bidirectional: the author of some abstract type is providing limited ways to access content; but no way to ‘put back’ changes to content.

None of this has persuaded me why the arrow points that way. The R.H. position is not a consumer of the value; it’s a binder – in fact a possibly-failing pattern that eventually leads to a binding. Neither am I persuaded why I’m forbidden from passing the argument explicitly. Nor do I dislike the syntax any less.

And indeed a 2000 version of the proposal had the ‘target’ on LHS (section 4) :

filtSeq :: (a -> Bool) -> Seq a -> Seq a
filtSeq p (Just (y,ys))!lview
            | p y        = lcons y (filtSeq p ys)
            | otherwise  = filtSeq p ys
filtSeq p Nothing!lview  = nil

I’m not liking that much better. My eye wants to see the ! as an infix operator spanning all the way to its left. (There’s no parens around the ! format.) That code is just crying out for a PatternSynonym IMO. (There was an early design from Wadler’s Views, that the paper compares, but a lot different to what eventually arrived ~15 years later.)

The 2000 paper goes on (section 7.1) to make the point that a ViewPattern can produce a familiar type (Maybe (..., ...)), so avoiding extra declarations (admittedly the draft design for Views was quite heavyweight at that time). Hmm:

  • Typically you do need an extra declaration anyway for the ViewPattern function.
  • Reusing a Maybe (or an Either, or tuples) seems to me an anti-feature: validation code becomes peppered with such types; far too easy to mix up the Maybes from different arguments and the type checker can’t help you.
  • So better that a PatternSynonym keeps the view within the same type as the source.

And chiefly:

  • ViewPatterns syntax is so heavyweight (whether there’s an arrow or something else, whichever way the arrow points).
  • The typing seems wrong: Just (..., ...) is not a constructor for a Seq. That’s particularly shown when you can go lv@(Just (..., ...)) and lv is not at all a Maybe.
  • The absent/implicit argument is baffling: I’m so used to reading code with partial applications, I have to keep reminding myself this isn’t really a partial.

OTOH, ViewPattern functions can take as arguments values already matched leftwards in the pattern/function match (the lookup env example); PatternSynonyms can only “give a view on a single value”. Hmm I wonder … (next post)

clunky env ((Find_in env) val1) ((Find_in env) val2) = val1 + val2

Find_in is a PatternSynonym – or to be more precise, (Find_in env) acts as the PatternSynonym; inside the parens is a use of the leftwards-bound env, not a fresh binding.

Of course I just plucked that double-parens syntax out of thin air. I’m thinking:

  • That syntax is valid in an expression, and is merely equivalent to applying the constructor to two arguments – as we’d want in a build context.
  • That syntax isn’t currently valid in a pattern match (you must put the constructor ‘flat’ with its arguments) – so it won’t upset existing code.

Or something like …

clunky env (Find_in env ? val1) (Find_in env ? val2) = val1 + val2

The ? can’t currently be part of a pattern, but I’m loath to co-opt another char with special meaning.

pattern (Find_in env) val <- lookup env -> Just val

Vars bound inside ( ... ) on LHS of pattern decl must appear on LHS of the view -> in the definition. But I want to root ViewPatterns out of the language entirely:

pattern (Find_in env) val <- _v  | Just val <- lookup env _v

The implementation can under-the-covers revert to the ViewPattern mechanism if it must.

There’s independent reasons for wanting pattern decls to be smarter: too often you need to split what could be a implicitly bidirectional decl (single equation with =) into explicitly bidir (two equations, the top with <-) because there’s no smarter way to express what currently can only be a ViewPattern.)