{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE Unsafe #-}
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
module Categorical.Dual.Example
( Coapplicative (..),
Comonad (..),
Distributive (..),
consume,
Algebra,
Coalgebra,
GAlgebra,
GCoalgebra,
ElgotAlgebra,
ElgotCoalgebra,
NewEither (..),
NewTuple (..),
NewEither' (..),
NewTuple' (..),
TestA,
DualA,
TestB,
DualB,
(>^>),
(<^<),
Mu (..),
Nu (..),
Fix (..),
cata,
ana,
exampleDuals,
testF,
testT,
testV,
testV',
testQ,
)
where
import Categorical.Dual
( dualType,
exportDuals,
importDuals,
labelDual,
labelSelfDual,
labelSemiDual,
makeDualClass,
makeDualDec,
)
import Categorical.Dual.Base (baseDuals)
import Categorical.Dual.Lens (lensDuals)
import safe Control.Applicative (Applicative, pure)
import safe Control.Arrow ((>>>))
import safe Control.Category ((.))
import safe Control.Monad (Monad, (=<<), (>>=))
import safe Data.Bool (Bool)
import safe Data.Char (Char, ord)
import safe Data.Either (Either (Right))
import safe Data.Foldable (Foldable)
import safe Data.Function (($))
import safe Data.Functor (Functor, fmap)
import safe Data.Int (Int)
import safe Data.Traversable (Traversable)
import safe Data.Traversable qualified as T
import safe Data.Void (Void)
import safe Prelude (undefined)
{-# HLINT ignore "Redundant bracket" #-}
importDuals baseDuals
importDuals lensDuals
testF :: $(dualType =<< [t|Int -> Char|])
testF :: Char -> Int
testF = Char -> Int
ord
testT :: $(dualType =<< [t|Either Int Char|])
testT :: (Int, Char)
testT = (Int
7, Char
'a')
testV :: $(dualType =<< [t|Either () Char|])
testV :: (Void, Char)
testV = (Void, Char)
forall a. HasCallStack => a
undefined :: (Void, Char)
testV' :: $(dualType =<< [t|((), Char)|])
testV' :: Either Void Char
testV' = Char -> Either Void Char
forall a b. b -> Either a b
Right Char
'a' :: Either Void Char
testQ :: $(dualType =<< [t|forall a b. Either (a -> Int) Char -> (Bool, Either Char (Int -> b))|])
testQ :: forall a b. Either Bool (Char, b -> Int) -> (Int -> a, Char)
testQ = Either Bool (Char, b -> Int) -> (Int -> a, Char)
forall {b} {a}. Either Bool (Char, b -> Int) -> (Int -> a, Char)
forall a. HasCallStack => a
undefined :: Either Bool (Char, b -> Int) -> (Int -> a, Char)
makeDualClass ''Monad "Comonad" [('(>>=), "=>>")]
labelSemiDual ''Foldable ''Functor
makeDualClass
''Traversable
"Distributive"
[ ('T.traverse, "cotraverse"),
('T.sequenceA, "distribute")
]
consume :: (Traversable g, Applicative f) => (g b -> a) -> g (f b) -> f a
consume :: forall (g :: Type -> Type) (f :: Type -> Type) b a.
(Traversable g, Applicative f) =>
(g b -> a) -> g (f b) -> f a
consume g b -> a
f = (g b -> a) -> f (g b) -> f a
forall a b. (a -> b) -> f a -> f b
forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
fmap g b -> a
f (f (g b) -> f a) -> (g (f b) -> f (g b)) -> g (f b) -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> Type) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. g (f b) -> f (g b)
forall (t :: Type -> Type) (f :: Type -> Type) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: Type -> Type) a. Applicative f => g (f a) -> f (g a)
T.sequenceA
makeDualDec [d|type Algebra f a = f a -> a|] "Coalgebra"
makeDualDec [d|type GAlgebra w f a = f (w a) -> a|] "GCoalgebra"
makeDualDec [d|type ElgotAlgebra w f a = w (f a) -> a|] "ElgotCoalgebra"
makeDualDec [d|newtype NewEither a b = NewEither (Either a b)|] "NewTuple"
makeDualDec [d|data NewEither' a b = NewEither' (Either a b)|] "NewTuple'"
makeDualDec [d|data family TestA a |] "DualA"
makeDualDec [d|type family TestB a |] "DualB"
makeDualDec
[d|
(>^>) :: (a -> b) -> (b -> c) -> a -> c
(>^>) = (>>>)
|]
"<^<"
labelSelfDual '($)
newtype Mu f = Mu (forall a. Algebra f a -> a)
data Nu f where Nu :: Coalgebra f a -> a -> Nu f
labelDual ''Mu ''Nu
newtype Fix f = Fix {forall (f :: Type -> Type). Fix f -> f (Fix f)
unfix :: f (Fix f)}
labelSelfDual ''Fix
labelDual 'Fix 'unfix
makeDualDec
[d|
cata :: (Functor f) => (f a -> a) -> Fix f -> a
cata f = f . fmap (cata f) . unfix
|]
"ana"
exportDuals "exampleDuals"