Skip to content
GitLab
Projects Groups Snippets
  • /
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
  • GHC GHC
  • Project information
    • Project information
    • Activity
    • Labels
    • Members
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 5,261
    • Issues 5,261
    • List
    • Boards
    • Service Desk
    • Milestones
    • Iterations
  • Merge requests 569
    • Merge requests 569
  • CI/CD
    • CI/CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Deployments
    • Deployments
    • Releases
  • Analytics
    • Analytics
    • Value stream
    • CI/CD
    • Code review
    • Insights
    • Issue
    • Repository
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell CompilerGlasgow Haskell Compiler
  • GHCGHC
  • Wiki
  • view patterns

view patterns · Changes

Page history
Enable syntax highlighting for view patterns authored Apr 13, 2019 by Ross Gardiner's avatar Ross Gardiner
Show whitespace changes
Inline Side-by-side
view-patterns.md
View page @ 2e13e628
......@@ -15,7 +15,7 @@ View patterns were introduced in GHC 6.10. This page has been revised to reflec
View patterns are a convenient way of pattern-matching against values of abstract types. For example, in a programming language implementation, we might represent the syntax of the types of the language as follows:
```wiki
```haskell
type Typ
data TypView = Unit
......@@ -32,7 +32,7 @@ The representation of `Typ` is held abstract, permitting implementations to use
In current Haskell, using this signature is a little inconvenient:
```wiki
```haskell
size :: Typ -> Integer
size t = case view t of
Unit -> 1
......@@ -46,7 +46,7 @@ In response, programmers sometimes eschew type abstraction in favor of revealing
View patterns permit calling the view function inside the pattern and matching against the result:
```wiki
```haskell
size (view -> Unit) = 1
size (view -> Arrow t1 t2) = size t1 + size t2
```
......@@ -54,7 +54,7 @@ View patterns permit calling the view function inside the pattern and matching a
That is, we add a new form of pattern, written
```wiki
```haskell
expression -> pattern
```
......@@ -76,8 +76,6 @@ However, sometimes modest syntactic sugar can have profound consequences. In thi
### Semantics
**Scoping** for *expr `->` *pat:
......@@ -86,13 +84,13 @@ However, sometimes modest syntactic sugar can have profound consequences. In thi
- In function definitions, variables bound by matching earlier curried arguments may be used in view pattern expressions in later arguments.
```wiki
```haskell
example :: (String -> Integer) -> String -> Bool
example f (f -> 4) = True
```
- Variables can be bound to the left in tuples and data constructors:
```wiki
```haskell
example :: ((String -> Integer,Integer), String) -> Bool
example ((f,_), f -> 4) = True
```
......@@ -117,7 +115,7 @@ We discuss some examples of pattern-matching abstract types and of other uses o
The requisite join-list example:
```wiki
```haskell
data JList a = Empty
| Single a
| Join (JList a) (JList a)
......@@ -132,7 +130,7 @@ Here we've chosen that the view type only exposes the cons/nil structure one lev
The implementation of the view:
```wiki
```haskell
view :: JList a -> JListView a
view Empty = Nil
view (Single a) = Cons a Empty
......@@ -146,7 +144,7 @@ Note the recursive uses of the view function in view patterns within its own def
An example of using it:
```wiki
```haskell
length :: JList a -> Integer
length (view -> Nil) = 0
length (view -> Cons x xs) = 1 + length xs
......@@ -155,7 +153,7 @@ An example of using it:
For more general sequences, `Data.Sequence` already defines the views from the left and from the right
```wiki
```haskell
data ViewL a
= EmptyL
| (:<) a (Seq a)
......@@ -177,7 +175,7 @@ that now may be used in view patterns.
Here's an alternate style of view definition: rather than mapping the abstract type to a single sum type, you provide outjections optionally inverting each constructor:
```wiki
```haskell
type Typ
outUnit : Typ -> Maybe ()
......@@ -189,7 +187,7 @@ Here's an alternate style of view definition: rather than mapping the abstract t
This view is used as follows:
```wiki
```haskell
size (outUnit -> Just _) = 1
size (outArrow -> Just (t1, t2)) = size t1 + size t2
```
......@@ -202,7 +200,7 @@ This style should be discouraged when the view is in fact a total operation, as
Here is a small module that allows to decompose sets with respect to a given element, deleting it hereby.
```wiki
```haskell
module Set(Set, empty, insert, delete, has) where
newtype Set a = S [a]
......@@ -228,7 +226,7 @@ Note the use of the previous argument `x` in later view patterns.
Sagonas et al describe an extension to Erlang that supports pattern-matching on bit-strings (["Application, implementation and performance evaluation of bit-stream programming in Erlang", PADL'07](http://user.it.uu.se/~kostis/Papers/index.html#Conference)). Suppose we had a parsing function thus:
```wiki
```haskell
bits :: Int -> ByteString -> Maybe (Word, ByteString)
-- (bits n bs) parses n bits from the front of bs, returning
-- the n-bit Word, and the remainder of bs
......@@ -237,7 +235,7 @@ Sagonas et al describe an extension to Erlang that supports pattern-matching on
Then we could write patterns like this:
```wiki
```haskell
parsePacket :: ByteString -> ...
parsePacket (bits 3 -> Just (n, (bits n -> Just (val, bs)))) = ...
```
......@@ -249,7 +247,7 @@ This parses 3 bits to get the value of `n`, and then parses `n` bits to get the
`(n+k)` patterns use the following view function:
```wiki
```haskell
np :: Num a => a -> a -> Maybe a
np k n | k <= n = Just (n-k)
| otherwise = Nothing
......@@ -258,7 +256,7 @@ This parses 3 bits to get the value of `n`, and then parses `n` bits to get the
They are used as follows:
```wiki
```haskell
fib :: Num a => a -> a
fib 0 = 1
fib 1 = 1
......@@ -270,7 +268,7 @@ Note the integration with type classes: the view function can be overloaded, and
`n+k` patterns are another a good opportunity for passing view data at run-time, as in:
```wiki
```haskell
example k (np k -> Just n) = ...
```
......@@ -279,7 +277,7 @@ Note the integration with type classes: the view function can be overloaded, and
View patterns can be used to pattern match against named constants:
```wiki
```haskell
errorVal :: Int -> Bool
errorVal = (== 4)
f (errorVal -> True) = ...
......@@ -290,7 +288,7 @@ View patterns can be used to pattern match against named constants:
A "both pattern" `pat1 & pat2` matches a value against both `pat1` and `pat2` and succeeds only when they both succeed. A special case is as-patterns, `x@p`, where the first pattern is a variable. Both patterns can be programmed using view patterns:
```wiki
```haskell
both : a -> (a,a)
both x = (x,x)
```
......@@ -298,7 +296,7 @@ A "both pattern" `pat1 & pat2` matches a value against both `pat1` and `pat2` an
And used as follows:
```wiki
```haskell
f (both -> (xs, h : t)) = h : (xs ++ t)
```
......@@ -310,7 +308,7 @@ And used as follows:
View patterns permit programming in an iterator style, where you name the result of a recursive call but not the term the call was made on. E.g.:
```wiki
```haskell
length [] = 0
length (_ : length -> n) = 1 + n
......@@ -335,7 +333,7 @@ Next, we describe two further syntactic extensions that we will implement.
Above, we saw several examples of view functions that return a `Maybe`, including:
```wiki
```haskell
np :: Num a => a -> a -> Maybe a
np k n | k <= n = Just (n-k)
| otherwise = Nothing
......@@ -344,7 +342,7 @@ Above, we saw several examples of view functions that return a `Maybe`, includin
which were used as follows:
```wiki
```haskell
fib (np 2 -> Just n) = fib (n + 1) + fib n
```
......@@ -352,14 +350,14 @@ which were used as follows:
We may implement a special syntax that makes the `Just` implicit, using *expr* `=>` *pat* for *expr* `-> Just` *pat*. An example use:
```wiki
```haskell
fib (np 2 => n) = fib (n + 1) + fib n
```
This syntax works very nicely with partial views:
```wiki
```haskell
size (outUnit => _) = 1
size (outArrow => (t1, t2)) = size t1 + size t2
```
......@@ -369,7 +367,7 @@ This syntax works very nicely with partial views:
A further syntactic extension would be to have implicit Maybes with implicit tupling: multiple patterns after the `=>` are implicitly tupled. Then you could write:
```wiki
```haskell
size (outArrow => t1 t2) = size t1 + size t2
```
......@@ -381,7 +379,7 @@ Total views have one syntactic disadvantage relative to the iterated-case style
The idea is that we distinguish a particular type class as a hook into the pattern compiler. The class has the following interface:
```wiki
```haskell
class View a b where
view :: a -> b
```
......@@ -390,7 +388,7 @@ The idea is that we distinguish a particular type class as a hook into the patte
Then, you can leave off the expresion in a view pattern, writing (`->` *pat*), to mean `view -> ` *pat*. For example:
```wiki
```haskell
size (-> Unit) = 1
size (-> Arrow t1 t2) = size t1 + size t2
```
......@@ -398,7 +396,7 @@ Then, you can leave off the expresion in a view pattern, writing (`->` *pat*), t
means
```wiki
```haskell
size (view -> Unit) = 1
size (view -> Arrow t1 t2) = size t1 + size t2
```
......@@ -409,7 +407,7 @@ for the overloaded `view`.
To use this mechanism, you add instances to `view`, as in:
```wiki
```haskell
instance View Typ TypView where
view = (the view function from above)
```
......@@ -425,7 +423,7 @@ Of course, you can only use one view function for each hidden-type/view-type pai
The above implementation of `size` is given the following type:
```wiki
```haskell
size :: View a TypView => a -> Int
```
......@@ -435,7 +433,7 @@ which may or may not be what you want. (For example, with nested view patterns,
Thus, it may be better to make one parameter of the type class determine the other (using associated type synonyms):
```wiki
```haskell
class View a where
type View a
view :: a -> View a
......@@ -444,7 +442,7 @@ Thus, it may be better to make one parameter of the type class determine the oth
or
```wiki
```haskell
class View b where
type Hidden b
view :: Hidden b -> a
......@@ -461,7 +459,7 @@ The downside of these versions is that you can only have one view for a type (wh
Due to type classes, checking for the "same" view pattern must be type-aware; the same source syntax cannot necessarily be commoned up:
```wiki
```haskell
class View a b where
view :: a -> b
......@@ -534,7 +532,7 @@ view constructors to appear in patterns only.
This proposal is substantially more complicated than the one above; in particular it
requires new form of top-level declaration for a view type. For example:
```wiki
```haskell
view Backwards a of [a] = [a] `Snoc` a | Nil
where
backwards [] = Nil
......@@ -562,7 +560,7 @@ to the different host language. Again, the value input feature is not supported
Erwig's proposal for active patterns renders the Set example like this:
```wiki
```haskell
data Set a = Empty | Add a (Set a)
pat Add' x _ =
......@@ -591,7 +589,7 @@ Active Destructors (ADs) are defined by a new form of top-level declaration.
Where we'd write
```wiki
```haskell
sing :: [a] -> a option
sing [x] = x
```
......@@ -599,7 +597,7 @@ Where we'd write
The equivalent active destructor would be
```wiki
```haskell
Sing x match [x]
```
......@@ -616,7 +614,7 @@ The value-input feature is supported, but only via a sort of mode declaration (i
They also introduce a combining form for ADs, to make a kind of and-pattern. For
example, suppose we had
```wiki
```haskell
Head x match (x:_)
Tail x match (_:xs)
......@@ -628,7 +626,7 @@ example, suppose we had
Here `(Head x)@(Tail ys)` is a pattern that matches *both* `(Head x)` and `(Tail ys)` against the argument, binding `x` and `ys` respectively. We can model that with view patterns:
```wiki
```haskell
headV (x:xs) = Just x
headV [] = Nothing
......@@ -641,7 +639,7 @@ Here `(Head x)@(Tail ys)` is a pattern that matches *both* `(Head x)` and `(Tail
An alternative to duplicating the value is to compose the functions:
```wiki
```haskell
(@) :: (a -> Maybe b) -> (a -> Maybe c) -> a -> Maybe (b,c)
(f @ g) x = do { b <- f x; c <- g x; return (b,c) }
......@@ -677,7 +675,7 @@ Here is [a full paper describing the design](http://blogs.msdn.com/dsyme/archive
The feature is implemented in F\# 1.9. Some code snippets are below.
```wiki
```fsharp
let (|Rect|) (x:complex) = (x.RealPart, x.ImaginaryPart)
let (|Polar|) (x:complex) = (x.Magnitude , x.Phase)
......@@ -697,7 +695,7 @@ The feature is implemented in F\# 1.9. Some code snippets are below.
And for views:
```wiki
```fsharp
open System
let (|Named|Array|Ptr|Param|) (typ : System.Type) =
......@@ -743,7 +741,7 @@ Reppy & Aiken, TR 92-1290, Cornell, June 1992.
The one way in which pattern synonyms are better than view patterns is thatn they define by-construction bi-directional maps. Example
```wiki
```haskell
data Term = Var String | Term String [Term]
-- 'const' introduces a pattern synonym
......@@ -757,7 +755,7 @@ The one way in which pattern synonyms are better than view patterns is thatn the
With pattern views, we'd have to write two functions for the "plus" view:
```wiki
```haskell
plus :: Term -> Term -> Term
plus a b = Term "+" [a,b]
......
Clone repository Edit sidebar

GHC Home

Joining In

Newcomers info
Mailing Lists & IRC
The GHC Team

Documentation

GHC Status Info
Working conventions
Building Guide
Commentary

Wiki

Title Index
Recent Changes