Last active
December 19, 2015 23:49
-
-
Save YoEight/6037352 to your computer and use it in GitHub Desktop.
Why Foo-error.hs doesn't compile while Foo-working.hs does ?
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| {-# LANGUAGE RankNTypes #-} | |
| type Foo = forall m. Monad m => Int -> m Int | |
| data Free f a = Pure a | |
| | Free (f (Free f a)) | |
| data Instr a = Instr Int a | |
| instance Functor Instr where | |
| fmap f (Instr i a) = Instr i (f a) | |
| cata :: Functor f => (a -> b) -> (f b -> b) -> Free f a -> b | |
| cata p _ (Pure a) = p a | |
| cata p f (Free m) = f $ fmap (cata p f) m | |
| eval :: Monad m => Free Instr () -> m Int | |
| eval instr = (cata pure free instr) 0 | |
| where | |
| pure _ x = return x | |
| free (Instr i k) = incr i k | |
| incr :: Int -> Foo -> Foo | |
| incr i k x = k (i + x) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| type Foo m = Int -> m Int | |
| data Free f a = Pure a | |
| | Free (f (Free f a)) | |
| data Instr a = Instr Int a | |
| instance Functor Instr where | |
| fmap f (Instr i a) = Instr i (f a) | |
| cata :: Functor f => (a -> b) -> (f b -> b) -> Free f a -> b | |
| cata p _ (Pure a) = p a | |
| cata p f (Free m) = f $ fmap (cata p f) m | |
| eval :: Monad m => Free Instr () -> m Int | |
| eval instr = (cata pure free instr) 0 | |
| where | |
| pure _ x = return x | |
| free (Instr i k) = incr i k | |
| incr :: Monad m => Int -> Foo m -> Foo m | |
| incr i k x = k (i + x) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
| Toto.hs:22:31: | |
| Could not deduce (t ~ (Int -> m2 Int)) | |
| from the context (Monad m) | |
| bound by the type signature for | |
| eval :: Monad m => Free Instr () -> m Int | |
| at Toto.hs:17:9-41 | |
| or from (Monad m1) | |
| bound by the inferred type of | |
| free :: Monad m1 => Instr t -> Int -> m1 Int | |
| at Toto.hs:22:5-31 | |
| or from (Monad m2) | |
| bound by a type expected by the context: Monad m2 => Int -> m2 Int | |
| at Toto.hs:22:24-31 | |
| `t' is a rigid type variable bound by | |
| the inferred type of free :: Monad m1 => Instr t -> Int -> m1 Int | |
| at Toto.hs:22:5 | |
| In the second argument of `incr', namely `k' | |
| In the expression: incr i k | |
| In an equation for `free': free (Instr i k) = incr i k | |
| Failed, modules loaded: none. |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment