extensible-0.4.7: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2017
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) -> (f :* xs) -> (g :| xs) -> 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

Wrapper k h => Wrapper k (Match k h r) Source # 

Associated Types

type Repr (Match k h r) (h :: Match k h r -> *) (v :: Match k h r) :: * Source #

Methods

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

Generic (Match k h r x) Source # 

Associated Types

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

Methods

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

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

Semigroup r => Semigroup (Match k h r x) Source # 

Methods

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

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

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

Monoid r => Monoid (Match k h r x) Source # 

Methods

mempty :: Match k h r x #

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

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

type Repr k (Match k h r) x Source # 
type Repr k (Match k h r) x = Repr k h x -> r
type Rep (Match k h r x) Source # 
type Rep (Match k h r x) = D1 (MetaData "Match" "Data.Extensible.Match" "extensible-0.4.7-9l1pejX5M0GGF8hg7qtV78" True) (C1 (MetaCons "Match" PrefixI True) (S1 (MetaSel (Just Symbol "runMatch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (h x -> r))))

match :: (Match h a :* xs) -> (h :| xs) -> 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 :: (h :| xs) -> (Match h a :* xs) -> a infix 0 Source #

Flipped match