Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Generics.Case
Description
Generic case analysis using generics-sop.
"Case analysis" functions are those which take one function for each constructor of a sum type,
examine a value of that type, and call the relevant function depending on which constructor was
used to build that type. Examples include maybe
, either
and bool
.
It's often useful to define similar functions on user-defined sum types, which is boring at best
and error-prone at worst. This module gives us these functions for any type which
implements Generic
.
For any single-constructor types, such as tuples, this gives us generic uncurrying without
any extra effort - see tupleL
, tuple3L
.
Example
Let's use These
from
these as an example.
First we need an instance of Generic
, which we can derive.
{-# LANGUAGE DeriveGeneric #-} import qualified GHC.Generics as G import Generics.SOP (Generic) data These a b = This a | That b | These a b deriving (Show, Eq, G.Generic) instance Generic (These a b) -- we could also do this using DeriveAnyClass
We're going to re-implement the case analysis function
these,
using gcase
. Our type has 3 constructors, so our function will have 4 arguments:
one for the These
we're analysing, and one function for each constructor.
The function is polymorphic in the result type.
these :: forall a b c. These a b -> _ -> _ -> _ -> c
What are the types of those 3 functions? For each constructor, we make a function type taking
one of each of the argument types, and returning our polymorphic result type c
:
these :: forall a b c. These a b -> (a -> c) -> -- for This (b -> c) -> -- for That (a -> b -> c) -> -- for These c
Finally, we add the implementation, which is just gcase
:
these :: forall a b c. These a b -> (a -> c) -> (b -> c) -> (a -> b -> c) -> c these = gcase
Note that we could have written the entire thing more succintly using Analysis
:
these :: forall a b c. Analysis (These a b) c these = gcase
Synopsis
- type Analysis a r = a -> Chains (Code a) r
- gcase :: forall a r. Generic a => Analysis a r
- maybeL :: forall a r. Maybe a -> r -> (a -> r) -> r
- eitherL :: forall a b r. Either a b -> (a -> r) -> (b -> r) -> r
- boolL :: forall r. Bool -> r -> r -> r
- tupleL :: forall a b r. (a, b) -> (a -> b -> r) -> r
- tuple3L :: forall a b c r. (a, b, c) -> (a -> b -> c -> r) -> r
- listL :: forall a r. [a] -> r -> (a -> [a] -> r) -> r
- nonEmptyL :: forall a r. NonEmpty a -> (a -> [a] -> r) -> r
Generic case analysis
type Analysis a r = a -> Chains (Code a) r Source #
The type of an analysis function on a generic type, in which the type comes before the functions.
You shouldn't ever need to create a function of this type manually; use gcase
.
You can exapand the type in a repl:
ghci> :k! Analysis (Maybe a) r Analysis (Maybe a) r :: * = Maybe a -> r -> (a -> r) -> r