{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Control.Newtype.Generics
( Newtype(..)
, op
, ala
, ala'
, under
, over
, under2
, over2
, underF
, overF
) where
import Control.Applicative
import Control.Arrow
import Data.Functor.Compose
import Data.Functor.Identity
#if MIN_VERSION_base(4,7,0)
import Data.Fixed
#endif
import Data.Monoid
import Data.Ord
#if MIN_VERSION_base(4,9,0)
import qualified Data.Semigroup
import Data.Semigroup (Min(..), Max(..), WrappedMonoid(..), Option(..))
#endif
import GHC.Generics
class GNewtype n where
type GO n :: *
gpack :: GO n -> n p
gunpack :: n p -> GO n
instance GNewtype (D1 d (C1 c (S1 s (K1 i a)))) where
type GO (D1 d (C1 c (S1 s (K1 i a)))) = a
gpack x = M1 (M1 (M1 (K1 x)))
gunpack (M1 (M1 (M1 (K1 x)))) = x
class Newtype n where
type O n :: *
type O n = GO (Rep n)
pack :: O n -> n
default pack :: (Generic n, GNewtype (Rep n), O n ~ GO (Rep n)) => O n -> n
pack = to . gpack
unpack :: n -> O n
default unpack :: (Generic n, GNewtype (Rep n), O n ~ GO (Rep n)) => n -> O n
unpack = gunpack . from
op :: (Newtype n,o ~ O n ) => (o -> n) -> n -> o
op _ = unpack
ala :: (Newtype n, Newtype n', o' ~ O n', o ~ O n)
=> (o -> n) -> ((o -> n) -> b -> n') -> (b -> o')
ala pa hof = ala' pa hof id
ala' :: (Newtype n, Newtype n', o' ~ O n', o ~ O n)
=> (o -> n) -> ((a -> n) -> b -> n') -> (a -> o) -> (b -> o')
ala' _ hof f = unpack . hof (pack . f)
under :: (Newtype n, Newtype n', o' ~ O n', o ~ O n)
=> (o -> n) -> (n -> n') -> (o -> o')
under _ f = unpack . f . pack
over :: (Newtype n, Newtype n', o' ~ O n', o ~ O n)
=> (o -> n) -> (o -> o') -> (n -> n')
over _ f = pack . f . unpack
under2 :: (Newtype n, Newtype n', o' ~ O n', o ~ O n)
=> (o -> n) -> (n -> n -> n') -> (o -> o -> o')
under2 _ f o0 o1 = unpack $ f (pack o0) (pack o1)
over2 :: (Newtype n, Newtype n', o' ~ O n', o ~ O n)
=> (o -> n) -> (o -> o -> o') -> (n -> n -> n')
over2 _ f n0 n1 = pack $ f (unpack n0) (unpack n1)
underF :: (Newtype n, Newtype n', o' ~ O n', o ~ O n, Functor f, Functor g)
=> (o -> n) -> (f n -> g n') -> (f o -> g o')
underF _ f = fmap unpack . f . fmap pack
overF :: (Newtype n, Newtype n', o' ~ O n', o ~ O n, Functor f, Functor g)
=> (o -> n) -> (f o -> g o') -> (f n -> g n')
overF _ f = fmap pack . f . fmap unpack
instance Newtype (WrappedMonad m a) where
type O (WrappedMonad m a) = m a
pack = WrapMonad
unpack (WrapMonad a) = a
instance Newtype (WrappedArrow a b c) where
type O (WrappedArrow a b c) = a b c
pack = WrapArrow
unpack (WrapArrow a) = a
instance Newtype (ZipList a) where
type O (ZipList a) = [a]
pack = ZipList
unpack (ZipList a) = a
instance Newtype (Kleisli m a b) where
type O (Kleisli m a b) = a -> m b
pack = Kleisli
unpack (Kleisli a) = a
instance Newtype (ArrowMonad a b) where
type O (ArrowMonad a b) = a () b
pack = ArrowMonad
unpack (ArrowMonad a) = a
#if MIN_VERSION_base(4,7,0)
instance Newtype (Fixed a) where
type O (Fixed a) = Integer
pack = MkFixed
unpack (MkFixed x) = x
#endif
instance Newtype (Compose f g a) where
type O (Compose f g a) = f (g a)
pack = Compose
unpack (Compose x) = x
instance Newtype (Const a x) where
type O (Const a x) = a
pack = Const
unpack (Const a) = a
instance Newtype (Identity a) where
type O (Identity a) = a
pack = Identity
unpack (Identity a) = a
instance Newtype (Dual a) where
type O (Dual a) = a
pack = Dual
unpack (Dual a) = a
instance Newtype (Endo a) where
type O (Endo a) = (a -> a)
pack = Endo
unpack (Endo a) = a
instance Newtype All where
type O All = Bool
pack = All
unpack (All x) = x
instance Newtype Any where
type O Any = Bool
pack = Any
unpack (Any x) = x
instance Newtype (Sum a) where
type O (Sum a) = a
pack = Sum
unpack (Sum a) = a
instance Newtype (Product a) where
type O (Product a) = a
pack = Product
unpack (Product a) = a
instance Newtype (First a) where
type O (First a) = Maybe a
pack = First
unpack (First a) = a
instance Newtype (Last a) where
type O (Last a) = Maybe a
pack = Last
unpack (Last a) = a
#if MIN_VERSION_base(4,8,0)
instance Newtype (Alt f a) where
type O (Alt f a) = f a
pack = Alt
unpack (Alt x) = x
#endif
#if MIN_VERSION_base(4,12,0)
instance Newtype (Ap f a) where
type O (Ap f a) = f a
pack = Ap
unpack = getAp
#endif
instance Newtype (Down a) where
type O (Down a) = a
pack = Down
unpack (Down a) = a
#if MIN_VERSION_base(4,9,0)
instance Newtype (Min a) where
type O (Min a) = a
pack = Min
unpack (Min a) = a
instance Newtype (Max a) where
type O (Max a) = a
pack = Max
unpack (Max a) = a
instance Newtype (Data.Semigroup.First a) where
type O (Data.Semigroup.First a) = a
pack = Data.Semigroup.First
unpack (Data.Semigroup.First a) = a
instance Newtype (Data.Semigroup.Last a) where
type O (Data.Semigroup.Last a) = a
pack = Data.Semigroup.Last
unpack (Data.Semigroup.Last a) = a
instance Newtype (WrappedMonoid m) where
type O (WrappedMonoid m) = m
pack = WrapMonoid
unpack (WrapMonoid m) = m
instance Newtype (Option a) where
type O (Option a) = Maybe a
pack = Option
unpack (Option x) = x
#endif