{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
module Distribution.Compat.Newtype (
Newtype (..),
ala,
alaf,
pack',
unpack',
) where
import Data.Functor.Identity (Identity (..))
import Data.Monoid (Sum (..), Product (..), Endo (..))
class Newtype n o | n -> o where
pack :: o -> n
unpack :: n -> o
instance Newtype (Identity a) a where
pack = Identity
unpack = runIdentity
instance Newtype (Sum a) a where
pack = Sum
unpack = getSum
instance Newtype (Product a) a where
pack = Product
unpack = getProduct
instance Newtype (Endo a) (a -> a) where
pack = Endo
unpack = appEndo
ala :: (Newtype n o, Newtype n' o') => (o -> n) -> ((o -> n) -> b -> n') -> (b -> o')
ala pa hof = alaf pa hof id
alaf :: (Newtype n o, Newtype n' o') => (o -> n) -> ((a -> n) -> b -> n') -> (a -> o) -> (b -> o')
alaf _ hof f = unpack . hof (pack . f)
pack' :: Newtype n o => (o -> n) -> o -> n
pack' _ = pack
unpack' :: Newtype n o => (o -> n) -> n -> o
unpack' _ = unpack