{-# LANGUAGE TypeFamilies #-}
module Data.Extensible.Match (
matchWith
, Match(..)
, match
, mapMatch
, caseOf) where
import Data.Extensible.Internal.Rig
import Data.Extensible.Class
import Data.Extensible.Product
import Data.Extensible.Sum
import Data.Extensible.Wrapper
import Data.Typeable (Typeable)
import Data.Profunctor.Unsafe
import GHC.Generics (Generic)
matchWith :: (forall x. f x -> g x -> r) -> xs :& f -> xs :/ g -> r
matchWith f p = \(EmbedAt i h) -> views (pieceAt i) f p h
{-# INLINE matchWith #-}
mapMatch :: (a -> b) -> Match h a x -> Match h b x
mapMatch f = Match #. (f.) .# runMatch
{-# INLINE mapMatch #-}
match :: xs :& Match h a -> xs :/ h -> a
match = matchWith runMatch
{-# INLINE match #-}
caseOf :: xs :/ h -> xs :& Match h a -> a
caseOf = flip match
{-# INLINE caseOf #-}
infix 0 `caseOf`
newtype Match h r x = Match { runMatch :: h x -> r }
deriving (Typeable, Generic, Semigroup, Monoid)
instance Wrapper h => Wrapper (Match h r) where
type Repr (Match h r) x = Repr h x -> r
_Wrapper = withIso _Wrapper $ \f g -> dimap ((. g) .# runMatch) (fmap (Match #. (. f)))
{-# INLINE _Wrapper #-}