mirror of
https://github.com/sayo-hs/heftia.git
synced 2024-11-23 02:42:06 +03:00
Rename the module from Control.Effect.Interpreter.Heftia.*
to Control.Monad.Hefty.*
.
This commit is contained in:
parent
ab78b12101
commit
7e837afcc3
@ -4,9 +4,6 @@
|
||||
|
||||
module Main where
|
||||
|
||||
import Control.Effect.Interpreter.Heftia.Reader (runReader)
|
||||
import Control.Effect.Interpreter.Heftia.ShiftReset (ShiftFix, evalShift, runShift_, unShiftBase)
|
||||
import Control.Effect.Interpreter.Heftia.State (evalState)
|
||||
import Control.Effect.Key (key)
|
||||
import Control.Monad.Extra (whenM)
|
||||
import Control.Monad.Hefty (
|
||||
@ -23,6 +20,9 @@ import Control.Monad.Hefty (
|
||||
type (+),
|
||||
type (:+:),
|
||||
)
|
||||
import Control.Monad.Hefty.Reader (runReader)
|
||||
import Control.Monad.Hefty.ShiftReset (ShiftFix, evalShift, runShift_, unShiftBase)
|
||||
import Control.Monad.Hefty.State (evalState)
|
||||
import Data.Effect.Key (type (#>))
|
||||
import Data.Effect.Reader (Ask, Local, ask, local)
|
||||
import Data.Effect.ShiftReset (Shift_, getCC, getCC_)
|
||||
|
@ -6,7 +6,6 @@
|
||||
module Main where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Control.Effect.Interpreter.Heftia.Provider (ProviderFix_, provide_, runProvider_)
|
||||
import Control.Monad.Hefty (
|
||||
Eff,
|
||||
Type,
|
||||
@ -18,6 +17,7 @@ import Control.Monad.Hefty (
|
||||
type (<|),
|
||||
type (~>),
|
||||
)
|
||||
import Control.Monad.Hefty.Provider (ProviderFix_, provide_, runProvider_)
|
||||
|
||||
data FileSystemF a where
|
||||
ReadFS :: FilePath -> FileSystemF String
|
||||
|
@ -9,8 +9,6 @@
|
||||
module Main where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Control.Effect.Interpreter.Heftia.Reader (runReader)
|
||||
import Control.Effect.Interpreter.Heftia.State (evalState)
|
||||
import Control.Monad (when)
|
||||
import Control.Monad.Hefty (
|
||||
Type,
|
||||
@ -38,6 +36,8 @@ import Control.Monad.Hefty (
|
||||
type (~>),
|
||||
type (~~>),
|
||||
)
|
||||
import Control.Monad.Hefty.Reader (runReader)
|
||||
import Control.Monad.Hefty.State (evalState)
|
||||
import Control.Monad.IO.Class (MonadIO)
|
||||
import Data.Effect.Reader (Ask, Local, ask, local)
|
||||
import Data.Effect.State (get, modify)
|
||||
|
@ -13,10 +13,6 @@ It can be confirmed that Heftia also realizes continuation-based semantics equiv
|
||||
module Main where
|
||||
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Effect.Interpreter.Heftia.Except (runCatch, runThrow)
|
||||
import Control.Effect.Interpreter.Heftia.NonDet (runChooseH, runNonDet)
|
||||
import Control.Effect.Interpreter.Heftia.State (evalState)
|
||||
import Control.Effect.Interpreter.Heftia.Writer (runTell, runWriterHPre)
|
||||
import Control.Monad.Hefty (
|
||||
interpret,
|
||||
makeEffectF,
|
||||
@ -27,6 +23,10 @@ import Control.Monad.Hefty (
|
||||
type (<|),
|
||||
type (~>),
|
||||
)
|
||||
import Control.Monad.Hefty.Except (runCatch, runThrow)
|
||||
import Control.Monad.Hefty.NonDet (runChooseH, runNonDet)
|
||||
import Control.Monad.Hefty.State (evalState)
|
||||
import Control.Monad.Hefty.Writer (runTell, runWriterHPre)
|
||||
import Data.Effect.Except (Catch, Throw, catch, throw)
|
||||
import Data.Effect.NonDet (ChooseH, Empty)
|
||||
import Data.Effect.State (State, get, put)
|
||||
|
@ -4,8 +4,8 @@
|
||||
|
||||
module Main where
|
||||
|
||||
import Control.Effect.Interpreter.Heftia.Writer (runTell, runWriterHPost, runWriterHPre)
|
||||
import Control.Monad.Hefty (liftIO, runEff, type (<:), type (<<:))
|
||||
import Control.Monad.Hefty.Writer (runTell, runWriterHPost, runWriterHPre)
|
||||
import Data.Effect.Writer (Tell, WriterH, censor, tell)
|
||||
|
||||
hello :: (Tell String <: m, Monad m) => m ()
|
||||
|
@ -7,10 +7,10 @@ module BenchCatch where
|
||||
|
||||
import Control.Carrier.Error.Either qualified as F
|
||||
import Control.Carrier.Reader qualified as F
|
||||
import Control.Effect.Interpreter.Heftia.Except qualified as H
|
||||
import Control.Effect.Interpreter.Heftia.Reader qualified as H
|
||||
import Control.Monad.Except qualified as M
|
||||
import Control.Monad.Hefty qualified as H
|
||||
import Control.Monad.Hefty.Except qualified as H
|
||||
import Control.Monad.Hefty.Reader qualified as H
|
||||
import Control.Monad.Identity qualified as M
|
||||
import Control.Monad.Reader qualified as M
|
||||
import Data.Effect.Except qualified as H
|
||||
|
@ -3,13 +3,13 @@
|
||||
|
||||
module BenchCoroutine where
|
||||
|
||||
import Control.Effect.Interpreter.Heftia.Coroutine qualified as H
|
||||
import Control.Effect.Interpreter.Heftia.Reader qualified as H
|
||||
import Control.Monad (forM)
|
||||
import Control.Monad.Freer qualified as FS
|
||||
import Control.Monad.Freer.Coroutine qualified as FS
|
||||
import Control.Monad.Freer.Reader qualified as FS
|
||||
import Control.Monad.Hefty qualified as H
|
||||
import Control.Monad.Hefty.Coroutine qualified as H
|
||||
import Control.Monad.Hefty.Reader qualified as H
|
||||
import Control.Mp.Eff qualified as Mp
|
||||
import Control.Mp.Util qualified as Mp
|
||||
import Data.Effect.Coroutine qualified as H
|
||||
|
@ -6,14 +6,14 @@ module BenchCountdown where
|
||||
|
||||
import Control.Carrier.Reader qualified as F
|
||||
import Control.Carrier.State.Strict qualified as F
|
||||
import Control.Effect.Interpreter.Heftia.Reader qualified as H
|
||||
import Control.Effect.Interpreter.Heftia.State qualified as H
|
||||
import Control.Ev.Eff qualified as E
|
||||
import Control.Ev.Util qualified as E
|
||||
import Control.Monad.Freer qualified as FS
|
||||
import Control.Monad.Freer.Reader qualified as FS
|
||||
import Control.Monad.Freer.State qualified as FS
|
||||
import Control.Monad.Hefty qualified as H
|
||||
import Control.Monad.Hefty.Reader qualified as H
|
||||
import Control.Monad.Hefty.State qualified as H
|
||||
import Control.Monad.Identity qualified as M
|
||||
import Control.Monad.Reader qualified as M
|
||||
import Control.Monad.State.Strict qualified as M
|
||||
|
@ -8,8 +8,6 @@ import Control.Algebra qualified as F
|
||||
import Control.Applicative (Alternative (empty, (<|>)))
|
||||
import Control.Carrier.NonDet.Church qualified as F
|
||||
import Control.Carrier.Reader qualified as F
|
||||
import Control.Effect.Interpreter.Heftia.NonDet qualified as H
|
||||
import Control.Effect.Interpreter.Heftia.Reader qualified as H
|
||||
import Control.Ev.Eff qualified as E
|
||||
import Control.Ev.Util qualified as E
|
||||
import Control.Monad (MonadPlus)
|
||||
@ -17,6 +15,8 @@ import Control.Monad.Freer qualified as FS
|
||||
import Control.Monad.Freer.NonDet qualified as FS
|
||||
import Control.Monad.Freer.Reader qualified as FS
|
||||
import Control.Monad.Hefty qualified as H
|
||||
import Control.Monad.Hefty.NonDet qualified as H
|
||||
import Control.Monad.Hefty.Reader qualified as H
|
||||
import Control.Monad.Identity qualified as M
|
||||
import Control.Monad.Logic qualified as M
|
||||
import Control.Monad.Reader qualified as M
|
||||
|
@ -69,22 +69,22 @@ library
|
||||
import: common-base
|
||||
|
||||
exposed-modules:
|
||||
Control.Effect.Interpreter.Heftia.Reader
|
||||
Control.Effect.Interpreter.Heftia.Writer
|
||||
Control.Effect.Interpreter.Heftia.State
|
||||
Control.Effect.Interpreter.Heftia.Except
|
||||
Control.Effect.Interpreter.Heftia.ShiftReset
|
||||
Control.Effect.Interpreter.Heftia.NonDet
|
||||
Control.Effect.Interpreter.Heftia.Coroutine
|
||||
Control.Effect.Interpreter.Heftia.Input
|
||||
Control.Effect.Interpreter.Heftia.Output
|
||||
Control.Effect.Interpreter.Heftia.Resource
|
||||
Control.Effect.Interpreter.Heftia.Unlift
|
||||
Control.Effect.Interpreter.Heftia.Provider
|
||||
Control.Effect.Interpreter.Heftia.KVStore
|
||||
Control.Effect.Interpreter.Heftia.Fresh
|
||||
Control.Effect.Interpreter.Heftia.Fail
|
||||
Control.Effect.Interpreter.Heftia.Concurrent.Timer
|
||||
Control.Monad.Hefty.Reader
|
||||
Control.Monad.Hefty.Writer
|
||||
Control.Monad.Hefty.State
|
||||
Control.Monad.Hefty.Except
|
||||
Control.Monad.Hefty.ShiftReset
|
||||
Control.Monad.Hefty.NonDet
|
||||
Control.Monad.Hefty.Coroutine
|
||||
Control.Monad.Hefty.Input
|
||||
Control.Monad.Hefty.Output
|
||||
Control.Monad.Hefty.Resource
|
||||
Control.Monad.Hefty.Unlift
|
||||
Control.Monad.Hefty.Provider
|
||||
Control.Monad.Hefty.KVStore
|
||||
Control.Monad.Hefty.Fresh
|
||||
Control.Monad.Hefty.Fail
|
||||
Control.Monad.Hefty.Concurrent.Timer
|
||||
|
||||
reexported-modules:
|
||||
Control.Monad.Hefty,
|
||||
|
@ -1,10 +1,10 @@
|
||||
-- SPDX-License-Identifier: MPL-2.0
|
||||
|
||||
module Control.Effect.Interpreter.Heftia.Concurrent.Timer where
|
||||
module Control.Monad.Hefty.Concurrent.Timer where
|
||||
|
||||
import Control.Concurrent.Thread.Delay qualified as Thread
|
||||
import Control.Effect.Interpreter.Heftia.Coroutine (runCoroutine)
|
||||
import Control.Effect.Interpreter.Heftia.State (evalState)
|
||||
import Control.Monad.Hefty.Coroutine (runCoroutine)
|
||||
import Control.Monad.Hefty.State (evalState)
|
||||
import Control.Monad.Hefty (
|
||||
interpose,
|
||||
interpret,
|
@ -1,6 +1,6 @@
|
||||
-- SPDX-License-Identifier: MPL-2.0
|
||||
|
||||
module Control.Effect.Interpreter.Heftia.Coroutine where
|
||||
module Control.Monad.Hefty.Coroutine where
|
||||
|
||||
import Control.Monad.Hefty.Interpret (interpretBy)
|
||||
import Control.Monad.Hefty.Types (Eff)
|
@ -10,7 +10,7 @@ Portability : portable
|
||||
|
||||
Interpreters for the t'Data.Effect.Except.Throw' / t'Data.Effect.Except.Catch' effects.
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Except where
|
||||
module Control.Monad.Hefty.Except where
|
||||
|
||||
import Control.Exception (Exception)
|
||||
import Control.Monad.Hefty (
|
@ -8,7 +8,7 @@ License : MPL-2.0 (see the LICENSE file)
|
||||
Maintainer : ymdfield@outlook.jp
|
||||
Portability : portable
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Fail where
|
||||
module Control.Monad.Hefty.Fail where
|
||||
|
||||
import Control.Monad.Hefty (Eff, interpret, liftIO, type (<|), type (~>))
|
||||
import Data.Effect.Fail (Fail (Fail))
|
@ -8,11 +8,11 @@ License : MPL-2.0 (see the LICENSE file)
|
||||
Maintainer : ymdfield@outlook.jp
|
||||
Portability : portable
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Fresh where
|
||||
module Control.Monad.Hefty.Fresh where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Control.Effect.Interpreter.Heftia.State (runState)
|
||||
import Control.Monad.Hefty (Eff, interpret, raiseUnder, type (<|), type (~>))
|
||||
import Control.Monad.Hefty.State (runState)
|
||||
import Data.Effect.Fresh (Fresh (Fresh))
|
||||
import Data.Effect.State (State, get, modify)
|
||||
import Numeric.Natural (Natural)
|
@ -8,11 +8,11 @@ License : MPL-2.0 (see the LICENSE file)
|
||||
Maintainer : ymdfield@outlook.jp
|
||||
Portability : portable
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Input where
|
||||
module Control.Monad.Hefty.Input where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Control.Effect.Interpreter.Heftia.State (evalState)
|
||||
import Control.Monad.Hefty (Eff, interpret, raiseUnder, type (~>))
|
||||
import Control.Monad.Hefty.State (evalState)
|
||||
import Data.Effect.Input (Input (Input))
|
||||
import Data.Effect.State (gets, put)
|
||||
import Data.List (uncons)
|
@ -12,11 +12,11 @@ This module provides handlers for the t`KVStore` effect, comes
|
||||
from [@Polysemy.KVStore@](https://hackage.haskell.org/package/polysemy-kvstore-0.1.3.0/docs/Polysemy-KVStore.html)
|
||||
in the @polysemy-kvstore@ package.
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.KVStore where
|
||||
module Control.Monad.Hefty.KVStore where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Control.Effect.Interpreter.Heftia.State (runState)
|
||||
import Control.Monad.Hefty (Eff, interpret, raiseUnder, type (<|), type (~>))
|
||||
import Control.Monad.Hefty.State (runState)
|
||||
import Data.Effect.KVStore (KVStore (LookupKV, UpdateKV))
|
||||
import Data.Effect.State (State, get, modify)
|
||||
import Data.Functor ((<&>))
|
@ -10,7 +10,7 @@ License : MPL-2.0 (see the LICENSE file)
|
||||
Maintainer : ymdfield@outlook.jp
|
||||
Portability : portable
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.NonDet where
|
||||
module Control.Monad.Hefty.NonDet where
|
||||
|
||||
import Control.Applicative (Alternative ((<|>)), empty, (<|>))
|
||||
#if ( __GLASGOW_HASKELL__ < 906 )
|
@ -8,12 +8,12 @@ License : MPL-2.0 (see the LICENSE file)
|
||||
Maintainer : ymdfield@outlook.jp
|
||||
Portability : portable
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Output where
|
||||
module Control.Monad.Hefty.Output where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Control.Effect.Interpreter.Heftia.State (runState)
|
||||
import Control.Effect.Interpreter.Heftia.Writer (handleTell)
|
||||
import Control.Monad.Hefty (Eff, interpret, interpretStateBy, raiseUnder, type (~>))
|
||||
import Control.Monad.Hefty.State (runState)
|
||||
import Control.Monad.Hefty.Writer (handleTell)
|
||||
import Data.Effect.Output (Output (Output))
|
||||
import Data.Effect.State (modify)
|
||||
import Data.Effect.Writer (Tell (Tell))
|
@ -7,7 +7,7 @@ Copyright : (c) 2024 Sayo Koyoneda
|
||||
License : MPL-2.0 (see the LICENSE file)
|
||||
Maintainer : ymdfield@outlook.jp
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Provider where
|
||||
module Control.Monad.Hefty.Provider where
|
||||
|
||||
import Control.Monad.Hefty (
|
||||
Eff,
|
@ -10,7 +10,7 @@ Portability : portable
|
||||
|
||||
Interpreters for the t'Ask' / t'Local' effects.
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Reader where
|
||||
module Control.Monad.Hefty.Reader where
|
||||
|
||||
import Control.Monad.Hefty (
|
||||
Eff,
|
@ -12,7 +12,7 @@ Portability : portable
|
||||
|
||||
An elaborator for the t'Control.Effect.Class.Resource.Resource' effect class.
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Resource where
|
||||
module Control.Monad.Hefty.Resource where
|
||||
|
||||
import Control.Effect (type (~>))
|
||||
import Control.Monad.Hefty.Interpret (interpretH)
|
@ -2,7 +2,7 @@
|
||||
-- License, v. 2.0. If a copy of the MPL was not distributed with this
|
||||
-- file, You can obtain one at https://mozilla.org/MPL/2.0/.
|
||||
|
||||
module Control.Effect.Interpreter.Heftia.ShiftReset where
|
||||
module Control.Monad.Hefty.ShiftReset where
|
||||
|
||||
import Control.Monad.Hefty (
|
||||
Eff,
|
@ -10,10 +10,9 @@ Portability : portable
|
||||
|
||||
Interpreter for the t'Data.Effect.State.State' effect.
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.State where
|
||||
module Control.Monad.Hefty.State where
|
||||
|
||||
import Control.Arrow ((>>>))
|
||||
import Control.Effect.Interpreter.Heftia.Reader (runAsk)
|
||||
import Control.Monad.Hefty (
|
||||
Eff,
|
||||
StateInterpreter,
|
||||
@ -29,6 +28,7 @@ import Control.Monad.Hefty (
|
||||
type (<|),
|
||||
type (~>),
|
||||
)
|
||||
import Control.Monad.Hefty.Reader (runAsk)
|
||||
import Data.Effect.Reader (Ask (Ask), ask)
|
||||
import Data.Effect.State (State (Get, Put), get, put)
|
||||
import Data.Functor ((<&>))
|
@ -8,7 +8,7 @@ License : MPL-2.0 (see the LICENSE file)
|
||||
Maintainer : ymdfield@outlook.jp
|
||||
Portability : portable
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Unlift where
|
||||
module Control.Monad.Hefty.Unlift where
|
||||
|
||||
import Control.Monad.Hefty (Eff, interpretH, runEff, send0, type (~>))
|
||||
import Data.Effect.Unlift (UnliftBase (WithRunInBase), UnliftIO)
|
@ -13,7 +13,7 @@ Portability : portable
|
||||
Interpreter and elaborator for the t'Data.Effect.Writer.Writer' effect class.
|
||||
See [README.md](https://github.com/sayo-hs/heftia/blob/master/README.md).
|
||||
-}
|
||||
module Control.Effect.Interpreter.Heftia.Writer where
|
||||
module Control.Monad.Hefty.Writer where
|
||||
|
||||
import Control.Monad.Hefty (
|
||||
Eff,
|
@ -2,8 +2,8 @@
|
||||
|
||||
module Test.Coroutine where
|
||||
|
||||
import Control.Effect.Interpreter.Heftia.Coroutine (runCoroutine)
|
||||
import Control.Monad (forM)
|
||||
import Control.Monad.Hefty.Coroutine (runCoroutine)
|
||||
import Control.Monad.Hefty.Interpret (runPure)
|
||||
import Control.Monad.Hefty.Types (Eff)
|
||||
import Data.Effect.Coroutine (Status (..), Yield, yield)
|
||||
|
@ -3,9 +3,9 @@
|
||||
module Test.Pyth where
|
||||
|
||||
import Control.Applicative (empty, (<|>))
|
||||
import Control.Effect.Interpreter.Heftia.NonDet (runChooseH, runNonDet)
|
||||
import Control.Monad (MonadPlus)
|
||||
import Control.Monad.Hefty.Interpret (runPure)
|
||||
import Control.Monad.Hefty.NonDet (runChooseH, runNonDet)
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
|
||||
search :: (MonadPlus m) => Int -> m (Int, Int, Int)
|
||||
|
@ -7,10 +7,6 @@ module Test.Semantics where
|
||||
|
||||
import Control.Applicative ((<|>))
|
||||
import Control.Effect (type (~>))
|
||||
import Control.Effect.Interpreter.Heftia.Except (runCatch, runThrow)
|
||||
import Control.Effect.Interpreter.Heftia.NonDet (runChooseH, runNonDet)
|
||||
import Control.Effect.Interpreter.Heftia.State (evalState)
|
||||
import Control.Effect.Interpreter.Heftia.Writer (runTell, runWriterHPre)
|
||||
import Control.Monad.Hefty (
|
||||
interpret,
|
||||
runPure,
|
||||
@ -19,6 +15,10 @@ import Control.Monad.Hefty (
|
||||
type (<<|),
|
||||
type (<|),
|
||||
)
|
||||
import Control.Monad.Hefty.Except (runCatch, runThrow)
|
||||
import Control.Monad.Hefty.NonDet (runChooseH, runNonDet)
|
||||
import Control.Monad.Hefty.State (evalState)
|
||||
import Control.Monad.Hefty.Writer (runTell, runWriterHPre)
|
||||
import Data.Effect.Except (Catch, Throw, catch, throw)
|
||||
import Data.Effect.NonDet (ChooseH, Empty)
|
||||
import Data.Effect.State (State, get, put)
|
||||
|
@ -3,8 +3,8 @@
|
||||
module Test.Writer where
|
||||
|
||||
import Control.Effect (type (<:), type (<<:))
|
||||
import Control.Effect.Interpreter.Heftia.Writer (runTell, runWriterHPost, runWriterHPre)
|
||||
import Control.Monad.Hefty.Interpret (runEff)
|
||||
import Control.Monad.Hefty.Writer (runTell, runWriterHPost, runWriterHPre)
|
||||
import Data.Effect.Writer (Tell, WriterH, censor, tell)
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user