module System.JBI.Tagged
( WithTagged (..)
, stripTag
, stripTags
, tag
, Tagged (..)
, proxy
) where
import Data.Coerce (Coercible, coerce)
import Data.Tagged
class WithTagged (g :: * -> *) where
withTaggedF :: (Coercible a a', Coercible b b', Functor f)
=> (a' -> f (g b')) -> Tagged t a -> f (g (Tagged t b))
default withTaggedF :: ( Coercible a a', Coercible b b', Functor f
, Coercible (g b') (g (Tagged t b))
, Coercible (g (Tagged t b)) (g b'))
=> (a' -> f (g b')) -> Tagged t a -> f (g (Tagged t b))
withTaggedF f = fmap coerce . f . coerce
tagInner :: Tagged t (g a) -> g (Tagged t a)
default tagInner :: ( Coercible (Tagged t (g a)) (g (Tagged t a))
, Coercible (g (Tagged t a)) (g a))
=> Tagged t (g a) -> g (Tagged t a)
tagInner = coerce
tagOuter :: g (Tagged t a) -> Tagged t (g a)
default tagOuter :: (Coercible (g (Tagged t a)) (Tagged t (g a)))
=> g (Tagged t a) -> Tagged t (g a)
tagOuter = coerce
instance WithTagged Maybe
instance WithTagged []
stripTag :: (Coercible a a') => Tagged t a -> a'
stripTag = coerce
stripTags :: (Coercible a a') => [Tagged t a] -> [a']
stripTags = coerce
tag :: (Coercible a a') => a -> Tagged t a'
tag = coerce