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
Flipping the argument order
maybe
, either
and bool
have a slightly different shape to these
: they take the datatype
(Maybe a
, Either a b
or Bool
) after the case functions, whereas these
(and generally any
analysis function implemented using gcase
) takes the datatype as its first argument, followed by
the case functions. This is due to the implementation, and is the recommended usage due to performance.
However, you may want your function to follow the same pattern as maybe
, since this is more ergonomic.
In this case you can use AnalysisR
and gcaseR
:
theseR :: forall a b c. (a -> c) -> (b -> c) -> (a -> b -> c) -> These a b -> c -- alternate signature: theseR :: forall a b c. AnalysisR (These a b) c theseR = gcaseR @(These a b)
Note that we need the TypeApplications
extension here. If you're really against this extension,
see gcaseR_
.
Synopsis
- type Analysis a r = a -> Chains (Code a) r
- gcase :: forall a r. Generic a => Analysis a r
- type AnalysisR a r = ChainsR (Code a) a r
- gcaseR :: forall a r. Generic a => AnalysisR a r
- gcaseR_ :: forall a r. Generic a => Proxy a -> AnalysisR a r
- maybeL :: forall a r. Maybe a -> r -> (a -> r) -> r
- maybeR :: forall a r. r -> (a -> r) -> Maybe a -> r
- eitherL :: forall a b r. Either a b -> (a -> r) -> (b -> r) -> r
- eitherR :: forall a b r. (a -> r) -> (b -> r) -> Either a b -> r
- boolL :: forall r. Bool -> r -> r -> r
- boolR :: forall r. r -> r -> Bool -> r
- tupleL :: forall a b r. (a, b) -> (a -> b -> r) -> r
- tupleR :: forall a b r. (a -> b -> r) -> (a, b) -> r
- tuple3L :: forall a b c r. (a, b, c) -> (a -> b -> c -> r) -> r
- tuple3R :: forall a b c r. (a -> b -> c -> r) -> (a, b, c) -> r
- listL :: forall a r. [a] -> r -> (a -> [a] -> r) -> r
- listR :: forall a r. r -> (a -> [a] -> r) -> [a] -> r
- nonEmptyL :: forall a r. NonEmpty a -> (a -> [a] -> r) -> r
- nonEmptyR :: forall a r. (a -> [a] -> r) -> NonEmpty a -> 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
Flipped argument order
gcaseR :: forall a r. Generic a => AnalysisR a r Source #
Generic case analysis, with the same shape as maybe
or either
. In other words this is the same
as gcase
, except the datatype comes after the analysis functions.
Note
This is undoubtedly more ergonomic, since it allows us to use partial application nicely:
let maybeToEither err = maybeR
(Left err) Right
in ...
However, this carries a slight performance impact. It will always be faster to use gcase
, so if
performance is critical in your use-case, use that. Then again, if performance is really critical,
you'll always be better off writing your analysis function manually; or just pattern-matching directly.