----------------------------------------------------------------------------- -- | -- Module : Data.Extensible.Union -- Copyright : (c) Fumiaki Kinoshita 2015 -- License : BSD3 -- -- Maintainer : Fumiaki Kinoshita -- Stability : experimental -- Portability : non-portable -- ------------------------------------------------------------------------ module Data.Extensible.Union ( ( *@ types. newtype Union fs a = Union { getUnion :: Flux a :| fs } deriving Typeable -- | fast fmap instance Functor (Union fs) where fmap f (Union (UnionAt pos s)) = Union (UnionAt pos (mapFlux f s)) {-# INLINE fmap #-} -- | /O(log n)/ Embed a value. liftU :: (f ∈ fs) => f a -> Union fs a liftU = Union . embed . Flux id {-# INLINE liftU #-} -- | Flipped data Flux a f where Flux :: (a -> b) -> f a -> Flux b f -- | 'fmap' for the content. mapFlux :: (a -> b) -> Flux a f -> Flux b f mapFlux f (Flux g m) = Flux (f . g) m {-# INLINE mapFlux #-} -- | Prepend a clause for @'Match' ('Flux' x)@ as well as (' (b -> x) -> a) -> Match (Flux x) a :* fs -> Match (Flux x) a :* (f ': fs) ( f m g {-# INLINE (