{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Functor.Prod
(
Prod(Unit, Cons)
, zeroTuple
, oneTuple
, fromProduct
, toProduct
, prod
, uncurryn
, type (++)
, Curried
)
where
import Control.Applicative(Alternative(..))
import Data.Functor.Product(Product(..))
import Data.Functor.Classes(Eq1(..), Ord1(..), Show1(..))
import Data.Kind (Type)
import qualified Data.Functor.Classes as FC
data Prod :: [k -> Type] -> k -> Type where
Unit :: Prod '[] a
Cons :: (f a) -> Prod fs a -> Prod (f ': fs) a
zeroTuple :: Prod '[] a
zeroTuple
= Unit
oneTuple :: f a -> Prod '[f] a
oneTuple fa
= Cons fa Unit
fromProduct :: Product f g a -> Prod '[f, g] a
fromProduct (Pair fa ga)
= Cons fa $ Cons ga Unit
toProduct :: Prod '[f, g] a -> Product f g a
toProduct (Cons fa (Cons ga Unit))
= Pair fa ga
prod :: Prod ls a -> Prod rs a -> Prod (ls ++ rs) a
l `prod` r =
case l of
Unit -> r
Cons la l' -> Cons la (l' `prod` r)
type family (++) l r :: [k] where
'[] ++ ys = ys
(x ': xs) ++ ys = x ': (xs ++ ys)
type family Curried t where
Curried (Prod '[] a -> r a) = r a
Curried (Prod (f ': fs) a -> r a) = f a -> Curried (Prod fs a -> r a)
uncurryn :: Curried (Prod fs a -> r a) -> Prod fs a -> r a
uncurryn fun = \case
Unit -> fun
Cons fa fs' ->
let fun' = fun fa
in uncurryn fun' fs'
instance Functor (Prod '[]) where
fmap _ Unit = Unit
instance (Functor f, Functor (Prod fs)) => Functor (Prod (f ': fs)) where
fmap f (Cons fa fas)
= Cons (fmap f fa) (fmap f fas)
instance Applicative (Prod '[]) where
pure _
= Unit
Unit <*> Unit
= Unit
instance (Applicative f, Applicative (Prod fs)) => Applicative (Prod (f ': fs)) where
pure a
= Cons (pure a) (pure a)
Cons f fs <*> Cons a as
= Cons (f <*> a) (fs <*> as)
instance Alternative (Prod '[]) where
empty
= Unit
Unit <|> Unit
= Unit
instance (Alternative f, Alternative (Prod fs)) => Alternative (Prod (f ': fs)) where
empty
= Cons empty empty
Cons f fs <|> Cons g gs
= Cons (f <|> g) (fs <|> gs)
instance Foldable (Prod '[]) where
foldMap _ = mempty
instance (Foldable f, Foldable (Prod fs)) => Foldable (Prod (f ': fs)) where
foldMap f (Cons fa fas)
= foldMap f fa `mappend` foldMap f fas
instance Traversable (Prod '[]) where
traverse _ Unit = pure Unit
instance (Traversable f, Traversable (Prod fs)) => Traversable (Prod (f ': fs)) where
traverse f (Cons fa fas)
= Cons <$> (traverse f fa) <*> (traverse f fas)
instance Eq1 (Prod '[]) where
liftEq _ Unit Unit = True
instance (Eq1 f, Eq1 (Prod fs)) => Eq1 (Prod (f ': fs)) where
liftEq eq (Cons l ls) (Cons r rs)
= liftEq eq l r && liftEq eq ls rs
instance Eq a => Eq (Prod '[] a) where
(==) = FC.eq1
instance (Eq1 f, Eq a, Eq1 (Prod fs)) => Eq (Prod (f ': fs) a) where
(==) = FC.eq1
instance Ord1 (Prod '[]) where
liftCompare _ Unit Unit = EQ
instance (Ord1 f, Ord1 (Prod fs)) => Ord1 (Prod (f ': fs)) where
liftCompare cmp (Cons l ls) (Cons r rs)
= liftCompare cmp l r `mappend` liftCompare cmp ls rs
instance Ord a => Ord (Prod '[] a) where
compare = FC.compare1
instance (Ord1 f, Ord a, Ord1 (Prod fs)) => Ord (Prod (f ': fs) a) where
compare = FC.compare1
instance Show1 (Prod '[]) where
liftShowsPrec _ _ _ Unit = showString "zeroTuple"
instance (Show1 f, Show1 (Prod fs)) => Show1 (Prod (f ': fs)) where
liftShowsPrec sp sl d = \case
(Cons fa Unit) ->
showParen (d > 10) $
showString "oneTuple " . liftShowsPrec sp sl 11 fa
(Cons fa fas) ->
showParen (d > 10) $
showString "oneTuple " . liftShowsPrec sp sl 11 fa
. showString " `prod` "
. liftShowsPrec sp sl 0 fas
instance Show a => Show (Prod '[] a) where
showsPrec = FC.showsPrec1
instance (Show1 f, Show a, Show1 (Prod fs)) => Show (Prod (f ': fs) a) where
showsPrec = FC.showsPrec1