Skip to content

Commit c5231e2

Browse files
committed
Breaking out Data.Inject
1 parent 618d880 commit c5231e2

File tree

5 files changed

+11
-57
lines changed

5 files changed

+11
-57
lines changed

README.md

Lines changed: 2 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -84,6 +84,8 @@
8484

8585
goMC :: forall f m a. (Monad m) => Natural f m -> FreeC f a -> m a
8686

87+
injC :: forall f g a. (Inject f g) => FreeC f a -> FreeC g a
88+
8789
iterM :: forall f m a. (Functor f, Monad m) => (forall a. f (m a) -> m a) -> Free f a -> m a
8890

8991
liftF :: forall f m a. (Functor f, Monad m, MonadFree f m) => f a -> m a
@@ -162,29 +164,6 @@
162164
lowerCoyoneda :: forall f a. (Functor f) => Coyoneda f a -> f a
163165

164166

165-
## Module Data.Inject
166-
167-
### Type Classes
168-
169-
class Inject f g where
170-
inj :: forall a. f a -> g a
171-
prj :: forall a. g a -> Maybe (f a)
172-
173-
174-
### Type Class Instances
175-
176-
instance injectLeft :: Inject f (Coproduct f g)
177-
178-
instance injectReflexive :: Inject f f
179-
180-
instance injectRight :: (Inject f g) => Inject f (Coproduct h g)
181-
182-
183-
### Values
184-
185-
injC :: forall f g a. (Inject f g) => FreeC f a -> FreeC g a
186-
187-
188167
## Module Data.Yoneda
189168

190169
### Types

bower.json

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@
3030
"purescript-transformers": "~0.3.0",
3131
"purescript-lazy": "~0.1.1",
3232
"purescript-foldable-traversable": "~0.1.4",
33-
"purescript-coproducts": "~0.1.0"
33+
"purescript-coproducts": "~0.1.0",
34+
"purescript-inject": "~0.0.2"
3435
}
3536
}

examples/TeletypeCoproduct.purs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,9 @@ module TeletypeCoproduct where
33
import Control.Apply ((*>))
44
import Control.Alt ((<|>))
55
import Control.Monad.Eff (Eff())
6-
import Control.Monad.Free (FreeC(), liftFC, goEffC)
6+
import Control.Monad.Free (FreeC(), liftFC, injC, goEffC)
77
import Data.Coyoneda (Natural())
8-
import Data.Inject (prj, injC)
8+
import Data.Inject (prj)
99
import Data.Functor.Coproduct (Coproduct())
1010
import Data.Maybe.Unsafe (fromJust)
1111
import Debug.Trace (Trace(), trace)

src/Control/Monad/Free.purs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module Control.Monad.Free
44
, MonadFree, wrap
55
, liftF, liftFC
66
, pureF, pureFC
7-
, mapF
7+
, mapF, injC
88
, iterM
99
, goM, goMC
1010
, go
@@ -16,6 +16,7 @@ import Control.Monad.Eff
1616
import Data.Coyoneda
1717
import Data.Either
1818
import Data.Function
19+
import Data.Inject (Inject, inj)
1920

2021
data Free f a = Pure a
2122
| Free (f (Free f a))
@@ -65,6 +66,9 @@ pureFC = liftFC <<< pure
6566
mapF :: forall f g a. (Functor f, Functor g) => Natural f g -> Free f a -> Free g a
6667
mapF t fa = either (\s -> Free <<< t $ mapF t <$> s) Pure (resume fa)
6768

69+
injC :: forall f g a. (Inject f g) => FreeC f a -> FreeC g a
70+
injC = mapF (liftCoyonedaT inj)
71+
6872
-- Note: can blow the stack!
6973
iterM :: forall f m a. (Functor f, Monad m) => (forall a. f (m a) -> m a) -> Free f a -> m a
7074
iterM _ (Pure a) = return a

src/Data/Inject.purs

Lines changed: 0 additions & 30 deletions
This file was deleted.

0 commit comments

Comments
 (0)