| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Generic.Match
Description
Name: Generic.Match Description: First class pattern matching for GHC.Generics. Copyright: 2020-2024 Samuel Schlesinger License: MIT
Synopsis
- match :: forall b r a x0 x1 x2 x3. (Generic b, Match a r, Rep b ~ D1 (MetaData x0 x1 x2 x3) a) => b -> Matcher b r
- class Match g r
- class Consume g
- type Matcher x r = Matcher' (StripData (Rep x)) r
- type family StripData g where ...
- type family Matcher' x r where ...
- type family Consumer x r where ...
- class Generic a
Pattern match on a Generic type
match :: forall b r a x0 x1 x2 x3. (Generic b, Match a r, Rep b ~ D1 (MetaData x0 x1 x2 x3) a) => b -> Matcher b r Source #
A first class pattern matching function for anything Generic, in the style of either and
maybe, but with the first argument being the thing you are pattern
matching on, as opposed to the last argument.
either f g x == match x f g
maybe r f x == match x r f
Beyond working for Maybe or Either, this function works on just
about any type you give to it, as long as that type has a Generic
instance. For example, this code is from the tests which are not
exported from this file:
data Ploop =
Clap Int Bool
| Splop [Integer] Float
| Flep [Int] [Float] [Bool]
deriving Generic
newtype X = X { unX :: Int } deriving Generic
data Klop = Cloop Klop
deriving Generic
tests :: Bool
tests = and
[ match True False True
, match False True False
, match (Left (5 :: Int)) (== 5) undefined
, match (Right ([1,2] :: [Int])) undefined ((== 2) . length)
, match (Clap 0 True) (i b -> i == 0 && b) undefined undefined
, match (X 1) (x -> x == 1)
, match (let x = Cloop x in x) (_ -> True)
]
There are other tests as well, at the type level, which I used to develop this library, and I think it makes sense to display those as well:
facts :: () facts = fold [ unitMatcher , boolMatcher , thingMatcher , pairMatcher , tripleMatcher , voidMatcher ] unitMatcher :: Matcher () r ~ (r -> r) => () unitMatcher = () boolMatcher :: Matcher Bool r ~ (r -> r -> r) => () boolMatcher = () data Thing = Thing Bool deriving Generic thingMatcher :: Matcher Thing r ~ ((Bool -> r) -> r) => () thingMatcher = () pairMatcher :: Matcher (Int, Bool) r ~ ((Int -> Bool -> r) -> r) => () pairMatcher = () tripleMatcher :: Matcher (Int, Int, Int) r ~ ((Int -> Int -> Int -> r) -> r) => () tripleMatcher = () voidMatcher :: Matcher Void r ~ r => () voidMatcher = ()
These may look strange to the reader, but the way to read them is that
the constraint to the left of the fat arrow must be true if I can
instantiate one of the terms in a context without assuming it. As
I instantiate all of them in that fold (possibly the only use of the
'()' monoid that I can think of, all of these constraints must be true.
This allowed me to develop this library by making instances that made
each new constraint I added true.
Type classes
The class that is used to inductively define the pattern matching for a particular generic type.
Minimal complete definition
match', const'
The typeclass used to consume a product inside of a Generic type.
Minimal complete definition
consume
Type families
type Matcher x r = Matcher' (StripData (Rep x)) r Source #
The type of a first class pattern match, having consumed the input.
type family Consumer x r where ... Source #
The type family that describes how to consume a product inside of a Generic type.
Re-exported from GHC.Generics
Representable types of kind *.
This class is derivable in GHC with the DeriveGeneric flag on.
A Generic instance must satisfy the following laws:
from.to≡idto.from≡id