Copyright | (c) Samuel Schlesinger 2020-2024 |
---|---|
License | MIT |
Maintainer | sgschlesinger@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Generic.Match
Description
Synopsis
- match :: forall b r xs. (Generic b, Match (Code b) r) => b -> Matcher b r
- class Match xs r
- class Consume xs
- type Matcher b r = Matcher' (Code b) r
- type family Matcher' (xs :: [[Type]]) r where ...
- type family Consumer (xs :: [Type]) (r :: Type) where ...
- class All (SListI :: [Type] -> Constraint) (Code a) => Generic a
Pattern match on a Generic
type
match :: forall b r xs. (Generic b, Match (Code b) r) => 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 (GHC.Generic, Generic) newtype X = X { unX :: Int } deriving (GHC.Generic, Generic) data Klop = Cloop Klop deriving (GHC.Generic, 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 (GHC.Generic, 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 b r = Matcher' (Code b) r Source #
The type of a first class pattern match, having consumed the input.
type family Consumer (xs :: [Type]) (r :: Type) where ... Source #
The type family that describes how to consume a product inside of a Generic
type.
Re-exported from Generics.SOP
class All (SListI :: [Type] -> Constraint) (Code a) => Generic a #
The class of representable datatypes.
The SOP approach to generic programming is based on viewing
datatypes as a representation (Rep
) built from the sum of
products of its components. The components of a datatype
are specified using the Code
type family.
The isomorphism between the original Haskell datatype and its
representation is witnessed by the methods of this class,
from
and to
. So for instances of this class, the following
laws should (in general) hold:
to
.
from
===id
:: a -> afrom
.
to
===id
::Rep
a ->Rep
a
You typically don't define instances of this class by hand, but rather derive the class instance automatically.
Option 1: Derive via the built-in GHC-generics. For this, you
need to use the DeriveGeneric
extension to first derive an
instance of the Generic
class from module GHC.Generics.
With this, you can then give an empty instance for Generic
, and
the default definitions will just work. The pattern looks as
follows:
import qualified GHC.Generics as GHC import Generics.SOP ... data T = ... deriving (GHC.Generic
, ...) instanceGeneric
T -- empty instanceHasDatatypeInfo
T -- empty, if you want/need metadata
Option 2: Derive via Template Haskell. For this, you need to
enable the TemplateHaskell
extension. You can then use
deriveGeneric
from module Generics.SOP.TH
to have the instance generated for you. The pattern looks as
follows:
import Generics.SOP import Generics.SOP.TH ... data T = ...deriveGeneric
''T -- derivesHasDatatypeInfo
as well
Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.
Non-standard instances:
It is possible to give Generic
instances manually that deviate
from the standard scheme, as long as at least
to
.
from
===id
:: a -> a
still holds.