mirror of
https://github.com/lexi-lambda/freer-simple.git
synced 2024-12-25 07:02:20 +03:00
fix: GHC 7.8 and 7.10 compatibility
This commit is contained in:
parent
0f553b2b99
commit
ce81c61670
@ -1,3 +1,7 @@
|
|||||||
|
# 0.2.4.1 (November 25, 2016)
|
||||||
|
|
||||||
|
* Restore GHC (7.8, 7.10) compatibility
|
||||||
|
|
||||||
# 0.2.4.0 (November 25, 2016)
|
# 0.2.4.0 (November 25, 2016)
|
||||||
|
|
||||||
* Internal reorg
|
* Internal reorg
|
||||||
|
@ -2,11 +2,16 @@
|
|||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
module Teletype where
|
module Teletype where
|
||||||
|
|
||||||
import Control.Monad.Freer
|
#if __GLASGOW_HASKELL__ < 710
|
||||||
|
import Control.Applicative (pure)
|
||||||
|
#endif
|
||||||
import System.Exit hiding (ExitSuccess)
|
import System.Exit hiding (ExitSuccess)
|
||||||
|
|
||||||
|
import Control.Monad.Freer
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
-- Effect Model --
|
-- Effect Model --
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
@ -42,11 +47,10 @@ runTeletypePure :: [String] -> Eff '[Teletype] w -> [String]
|
|||||||
runTeletypePure inputs req =
|
runTeletypePure inputs req =
|
||||||
reverse . snd $ run (handleRelayS (inputs, []) (\s _ -> pure s) go req)
|
reverse . snd $ run (handleRelayS (inputs, []) (\s _ -> pure s) go req)
|
||||||
where
|
where
|
||||||
go
|
go :: ([String], [String])
|
||||||
:: ([String], [String])
|
-> Teletype v
|
||||||
-> Teletype v
|
-> (([String], [String]) -> Arr '[] v ([String], [String]))
|
||||||
-> (([String], [String]) -> Arr '[] v ([String], [String]))
|
-> Eff '[] ([String], [String])
|
||||||
-> Eff '[] ([String], [String])
|
|
||||||
go (is, os) (PutStrLn msg) q = q (is, msg : os) ()
|
go (is, os) (PutStrLn msg) q = q (is, msg : os) ()
|
||||||
go (i:is, os) GetLine q = q (is, os) i
|
go (i:is, os) GetLine q = q (is, os) i
|
||||||
go ([], _) GetLine _ = error "Not enough lines"
|
go ([], _) GetLine _ = error "Not enough lines"
|
||||||
|
@ -1,5 +1,5 @@
|
|||||||
name: freer
|
name: freer
|
||||||
version: 0.2.4.0
|
version: 0.2.4.1
|
||||||
synopsis: Implementation of the Freer Monad
|
synopsis: Implementation of the Freer Monad
|
||||||
license: BSD3
|
license: BSD3
|
||||||
license-file: LICENSE
|
license-file: LICENSE
|
||||||
@ -10,8 +10,8 @@ homepage: https://gitlab.com/queertypes/freer
|
|||||||
bug-reports: https://gitlab.com/queertypes/freer/issues
|
bug-reports: https://gitlab.com/queertypes/freer/issues
|
||||||
category: Control
|
category: Control
|
||||||
build-type: Simple
|
build-type: Simple
|
||||||
cabal-version: >=1.18
|
cabal-version: >=1.10
|
||||||
tested-with: GHC==7.10.2
|
tested-with: GHC==7.10.3, GHC==8.0.1, GHC==7.8.4
|
||||||
description:
|
description:
|
||||||
|
|
||||||
Freer is an implementation of "Freer Monads, More Extensible
|
Freer is an implementation of "Freer Monads, More Extensible
|
||||||
@ -64,7 +64,7 @@ executable freer-examples
|
|||||||
, NonDetEff
|
, NonDetEff
|
||||||
, Teletype
|
, Teletype
|
||||||
, Trace
|
, Trace
|
||||||
build-depends: base >=4.7 && <5
|
build-depends: base
|
||||||
, freer
|
, freer
|
||||||
hs-source-dirs: examples/src
|
hs-source-dirs: examples/src
|
||||||
ghc-options: -Wall
|
ghc-options: -Wall
|
||||||
|
@ -1,6 +1,7 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
{-|
|
{-|
|
||||||
Module : Control.Monad.Freer
|
Module : Control.Monad.Freer
|
||||||
Description : Freer - an extensible effects library
|
Description : Freer - an extensible effects library
|
||||||
@ -28,6 +29,10 @@ module Control.Monad.Freer (
|
|||||||
msplit
|
msplit
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
#if __GLASGOW_HASKELL__ < 710
|
||||||
|
import Control.Applicative (pure)
|
||||||
|
#endif
|
||||||
|
|
||||||
import Control.Monad.Freer.Internal
|
import Control.Monad.Freer.Internal
|
||||||
|
|
||||||
runNat
|
runNat
|
||||||
|
@ -25,7 +25,7 @@ instance (r ~ (t ': r')) => Member' t r 'Z where
|
|||||||
prj' _ (UNow x) = Just x
|
prj' _ (UNow x) = Just x
|
||||||
prj' _ _ = Nothing
|
prj' _ _ = Nothing
|
||||||
|
|
||||||
instance (r ~ (t' ': r' : rs'), Member' t (r' : rs') n) => Member' t r ('S n) where
|
instance (r ~ (t' ': r' ': rs'), Member' t (r' ': rs') n) => Member' t r ('S n) where
|
||||||
inj' _ = UNext . inj' (P::P n)
|
inj' _ = UNext . inj' (P::P n)
|
||||||
prj' _ (UNow _) = Nothing
|
prj' _ (UNow _) = Nothing
|
||||||
prj' _ (UNext x) = prj' (P::P n) x
|
prj' _ (UNext x) = prj' (P::P n) x
|
||||||
@ -73,5 +73,3 @@ instance (Functor f) => Functor (Union '[f]) where
|
|||||||
instance (Functor f1, Functor (Union (f2 ': fs))) =>
|
instance (Functor f1, Functor (Union (f2 ': fs))) =>
|
||||||
Functor (Union (f1 ': f2 ': fs)) where
|
Functor (Union (f1 ': f2 ': fs)) where
|
||||||
fmap f = either (weaken . fmap f) (inj . fmap f) . decomp
|
fmap f = either (weaken . fmap f) (inj . fmap f) . decomp
|
||||||
|
|
||||||
|
|
||||||
|
Loading…
Reference in New Issue
Block a user