extensible-0.9: Extensible, efficient, optics-friendly data types and effects
Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Match

Description

Pattern matching

Synopsis

Documentation

matchWith :: (forall x. f x -> g x -> r) -> (xs :& f) -> (xs :/ g) -> r Source #

Retrieve the contents so that they matches and pass both to the given function.

newtype Match h r x Source #

Turn a wrapper type into a clause for it.

Constructors

Match 

Fields

Instances

Instances details
Wrapper h => Wrapper (Match h r :: k -> Type) Source # 
Instance details

Defined in Data.Extensible.Match

Associated Types

type Repr (Match h r) v Source #

Methods

_Wrapper :: forall f p (v :: k0). (Functor f, Profunctor p) => Optic' p f (Match h r v) (Repr (Match h r) v) Source #

wrap :: forall (v :: k0). Repr (Match h r) v -> Match h r v Source #

unwrap :: forall (v :: k0). Match h r v -> Repr (Match h r) v Source #

Generic (Match h r x) Source # 
Instance details

Defined in Data.Extensible.Match

Associated Types

type Rep (Match h r x) :: Type -> Type #

Methods

from :: Match h r x -> Rep (Match h r x) x0 #

to :: Rep (Match h r x) x0 -> Match h r x #

Semigroup r => Semigroup (Match h r x) Source # 
Instance details

Defined in Data.Extensible.Match

Methods

(<>) :: Match h r x -> Match h r x -> Match h r x #

sconcat :: NonEmpty (Match h r x) -> Match h r x #

stimes :: Integral b => b -> Match h r x -> Match h r x #

Monoid r => Monoid (Match h r x) Source # 
Instance details

Defined in Data.Extensible.Match

Methods

mempty :: Match h r x #

mappend :: Match h r x -> Match h r x -> Match h r x #

mconcat :: [Match h r x] -> Match h r x #

type Repr (Match h r :: k -> Type) (x :: k) Source # 
Instance details

Defined in Data.Extensible.Match

type Repr (Match h r :: k -> Type) (x :: k) = Repr h x -> r
type Rep (Match h r x) Source # 
Instance details

Defined in Data.Extensible.Match

type Rep (Match h r x) = D1 ('MetaData "Match" "Data.Extensible.Match" "extensible-0.9-Kdnj6Oi23WF73T2oBT60p1" 'True) (C1 ('MetaCons "Match" 'PrefixI 'True) (S1 ('MetaSel ('Just "runMatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (h x -> r))))

match :: (xs :& Match h a) -> (xs :/ h) -> a Source #

O(1) Perform pattern matching.

mapMatch :: (a -> b) -> Match h a x -> Match h b x Source #

Applies a function to the result of Match.

caseOf :: (xs :/ h) -> (xs :& Match h a) -> a infix 0 Source #

Flipped match