[fix] Move basic types and classes about effects into the classy-effects-base package.

This commit is contained in:
Yamada Ryo 2023-08-29 13:27:23 +09:00
parent 04360da6ab
commit f62fc4d18b
No known key found for this signature in database
GPG Key ID: AAE3C7A542B02DBF
13 changed files with 19 additions and 43 deletions

View File

@ -53,14 +53,12 @@ source-repository head
library
exposed-modules:
Control.Hefty
Control.Heftia
Control.Heftia.Final
Control.Heftia.Final.Naked
Control.Heftia.Trans
Control.Heftia.Trans.Final
Control.Heftia.Trans.Final.Naked
Control.Free
Control.Freer
Control.Freer.Trans
Control.Monad.Trans.Heftia
@ -79,6 +77,7 @@ library
-- other-extensions:
build-depends:
base ^>= 4.16.4.0,
classy-effects-base ^>= 0.1,
mtl,
free,
natural-transformation,

View File

@ -1,5 +0,0 @@
module Control.Free where
import Data.Kind (Type)
type Instruction = Type -> Type

View File

@ -1,6 +1,6 @@
module Control.Freer.Trans where
import Control.Free (Instruction)
import Control.Effect.Class (Instruction)
import Data.Kind (Type)
newtype FreerT (f :: (Type -> Type) -> Instruction -> Type -> Type) ins m a = FreerT

View File

@ -3,7 +3,8 @@
module Control.Heftia where
import Control.Hefty (HFunctor, LiftIns, hmap, unliftIns)
import Control.Effect.Class (LiftIns, unliftIns)
import Control.Effect.Class.HFunctor (HFunctor, hmap)
import Control.Natural (type (~>))
import Data.Hefty.Union (Member, Union, decomp, inject, project, weakenL, weakenR, weakenSig, type (<:))

View File

@ -4,7 +4,8 @@
module Control.Heftia.Final where
import Control.Applicative (Alternative, empty, (<|>))
import Control.Hefty (HFunctor, Signature, hmap)
import Control.Effect.Class (Signature)
import Control.Effect.Class.HFunctor (HFunctor, hmap)
import Control.Monad (MonadPlus (mplus, mzero))
import Control.Natural (type (~>))
import Data.Constraint (Class, cls, (\\))

View File

@ -1,8 +1,9 @@
module Control.Heftia.Final.Naked where
import Control.Effect.Class (Signature)
import Control.Effect.Class.HFunctor (HFunctor, hmap)
import Control.Freer (Freer, liftIns, retractF)
import Control.Heftia.Final (HeftiaFinal (HeftiaFinal), Noop)
import Control.Hefty (HFunctor, Signature, hmap)
import Control.Natural (type (~>))
import Data.Hefty.Sum (type (+) (L, R))

View File

@ -2,8 +2,8 @@
module Control.Heftia.Trans where
import Control.Effect.Class.HFunctor (HFunctor, hmap)
import Control.Heftia (Heftia, liftSig)
import Control.Hefty (HFunctor, hmap)
import Control.Monad.Identity (IdentityT (IdentityT), runIdentityT)
import Control.Natural (type (~>))

View File

@ -4,8 +4,9 @@
module Control.Heftia.Trans.Final where
import Control.Applicative (Alternative)
import Control.Effect.Class (LiftIns (LiftIns))
import Control.Effect.Class.HFunctor (HFunctor, hmap)
import Control.Heftia.Final (HeftiaFinal (HeftiaFinal), liftSigFinal, weakenHeftiaFinal)
import Control.Hefty (HFunctor, LiftIns (LiftIns), hmap)
import Control.Monad (MonadPlus)
import Control.Natural (type (~>))
import Data.Constraint (Class)

View File

@ -1,5 +1,7 @@
module Control.Heftia.Trans.Final.Naked where
import Control.Effect.Class (LiftIns, Signature)
import Control.Effect.Class.HFunctor (HFunctor, hmap)
import Control.Freer (Freer, liftIns, retractF)
import Control.Heftia.Final (Noop)
import Control.Heftia.Final.Naked (HeftiaFinalN, nakeHeftiaFinal, wearHeftiaFinal)
@ -12,7 +14,6 @@ import Control.Heftia.Trans.Final (
runHeftiaFinalT,
unHeftiaFinalT,
)
import Control.Hefty (HFunctor, LiftIns, Signature, hmap)
import Data.Hefty.Sum (type (+) (L, R))
newtype HeftiaFinalTN (h :: Signature) f a = HeftiaFinalTN

View File

@ -1,26 +0,0 @@
module Control.Hefty where
import Data.Kind (Type)
{- | The class for /signature/s (datatypes of higher-order effect).
Come from [heft-lang\/POPL2023\/haskell\/src\/Hefty.hs]
(https://github.com/heft-lang/POPL2023/blob/74afe1d5ce0b491cffe40cc5c73a2a5ee6a94d9c/haskell/src/Hefty.hs#L9-L10).
-}
class HFunctor h where
-- | Hoist the monad underlying a /signature/.
hmap :: (forall x. f x -> g x) -> h f a -> h g a
{- | Lift an /instruction/ (a datatype of first-order effect) to a /signature/
(a datatype of higher-order effect).
Come from [heft-lang\/POPL2023\/haskell\/src\/Elab.hs]
(https://github.com/heft-lang/POPL2023/blob/74afe1d5ce0b491cffe40cc5c73a2a5ee6a94d9c/haskell/src/Elab.hs#L9-L10).
-}
newtype LiftIns ins (f :: Type -> Type) (a :: Type) = LiftIns {unliftIns :: ins a}
deriving stock (Functor, Foldable, Traversable)
instance HFunctor (LiftIns ins) where
hmap _ = LiftIns . unliftIns
type Signature = (Type -> Type) -> Type -> Type

View File

@ -1,7 +1,8 @@
module Control.Monad.Trans.Heftia where
import Control.Effect.Class (Signature)
import Control.Effect.Class.HFunctor (HFunctor)
import Control.Heftia.Trans (TransHeftia, hoistHeftia, interpretT, liftLower)
import Control.Hefty (HFunctor, Signature)
import Control.Monad.Cont (ContT)
import Control.Monad.Trans (MonadTrans, lift)
import Control.Natural (type (~>))

View File

@ -2,9 +2,10 @@
module Data.Hefty.Sum where
import Control.Effect.Class (LiftIns, Signature)
import Control.Effect.Class.HFunctor (HFunctor, hmap)
import Control.Heftia (liftSig, translateH)
import Control.Heftia.Trans (TransHeftia, interpretT)
import Control.Hefty (HFunctor, LiftIns, Signature, hmap)
import Data.Free.Sum (NopF)
import Data.Hefty.Union (HFunctorUnion, Union, type (<:))
import Data.Hefty.Union qualified as U

View File

@ -2,7 +2,8 @@
module Data.Hefty.Union where
import Control.Hefty (HFunctor, Signature)
import Control.Effect.Class (Signature)
import Control.Effect.Class.HFunctor (HFunctor)
import Control.Natural (type (~>))
import Data.Kind (Constraint)