total-1.0.1: Exhaustive pattern matching using lenses, traversals, and prisms

Safe HaskellSafe-Infered

Lens.Family.Total

Contents

Description

This module lets you exhaustively pattern match on types using Lenses, Traversals, or Prisms.

Here's an example use of this library:

 import Lens.Family.Total
 import Lens.Family.Stock

 total :: Either Char Int -> String       -- Same as:
 total = _case                            -- total = \case
     & on _Left  (\c -> replicate 3  c )  --     Left  c -> replicate 3 c
     & on _Right (\n -> replicate n '!')  --     Right n -> replicate n '!'

Our example function pattern matches exhaustively on the Either type using the _Left and _Right prisms:

>>> example (Left 'X')
"XXX"
>>> example (Right 2)
"!!"

The types ensure that the above function is total. For example, if you omit the _Right branch:

 partial :: Either Char Int -> String
 partial = _case
     & on _Left  (\c -> replicate 3  c )

... then you will get the following type error:

 No instance for (Empty Int) arising from a use of ‘_case’
 In the first argument of ‘(&)’, namely ‘_case’
 In the expression: _case & on _Left (\ c -> replicate 3 c)
 In an equation for ‘partial’:
     partial = _case & on _Left (\ c -> replicate 3 c)

That type error means that you didn't pattern match on the branch with the Int.

You can also implement exhaustive pattern matching for your own data types with Traversals or Prisms. However, this only works if you have one type variable for each branch of your type:

 {-# LANGUAGE DeriveGeneric   #-}
 {-# LANGUAGE TemplateHaskell #-}

 import Control.Lens.TH
 import GHC.Generics (Generic)
 import Lens.Family.Total

 data Example a b c = C1 a | C2 b | C3 c deriving (Generic)

 makePrisms ''Example

 instance (Empty a, Empty b, Empty c) => Empty (Example a b c)

 example :: Example String Char Int -> String  -- Same as:
 example = _case                               -- example = \case
     & on _C1 (\s -> s              )          --     C1 s -> s
     & on _C2 (\c -> replicate 3  c )          --     C2 c -> replicate 3  c
     & on _C3 (\n -> replicate n '!')          --     C3 n -> replicate n '!'

There is no way to prove that the pattern match is exhaustive unless there is a type parameter for every branch. This is because each successive pattern match Voids out that branch's type parameter to prove that the branch no longer needs to be handled. _case just verifies that all type parameters are Void.

You can even pattern match using Lenses, too:

 example :: (Int, Char) -> String     -- Same as:
 example = _case                      -- example = \case
     & on _1 (\n -> replicate n '1')  --     (n, _) -> replicate n '1'

... and of course the identity lens (id) works, too:

 example :: (Int, Char) -> String        -- Same as:
 example = _case                         -- example = \case
     & on id (\(n, c) -> replicate n c)  --     (n, c) -> replicate n c

Synopsis

Documentation

class Empty a whereSource

A type class for uninhabited types

Methods

impossible :: a -> xSource

Instances

Empty Void 
(Empty a, Empty b) => Empty (Either a b) 
Empty a => Empty (a, b) 

_case :: Empty a => a -> xSource

Synonym for impossible, used to check if a pattern match is exhaustive

on :: ((a -> Either a Void) -> i -> Either l r) -> (l -> o) -> (r -> o) -> i -> oSource

Pattern match on a Traversal

(&) :: a -> (a -> b) -> bSource

Operator for post-fix function application

Re-exports

data Void

A logically uninhabited data type.

Instances

Eq Void 
Data Void 
Ord Void 
Read Void

Reading a Void value is always a parse error, considering Void as a data type with no constructors.

Show Void 
Ix Void 
Typeable Void 
Generic Void 
Exception Void 
Hashable Void 
Semigroup Void 
Empty Void