Skip to content

Instantly share code, notes, and snippets.

@sordina
Created January 28, 2016 10:56
Show Gist options
  • Save sordina/bacb79d051abdfd0f86c to your computer and use it in GitHub Desktop.
Save sordina/bacb79d051abdfd0f86c to your computer and use it in GitHub Desktop.
Excerpts from Oleg's Freer Monads - http://okmij.org/ftp/Haskell/extensible/more.pdf
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
import Control.Monad
{-
data ReaderWriter i o x = Get (i -> x)
| Put o (() -> x)
deriving Functor
-}
data Free f a where
FPure :: a -> Free f a
FImpure :: f (Free f a) -> Free f a
instance Functor (Free f) where
fmap = undefined
instance Applicative (Free f) where
pure = undefined
(<*>) = undefined
instance Functor f => Monad (Free f) where
return = FPure
FPure a >>= k = k a
FImpure f >>= k = FImpure (fmap (>>= k) f)
data FFree f a where
Pure :: a -> FFree f a
Impure :: f x -> (x -> FFree f a) -> FFree f a
data FReaderWriter i o x where
Get :: FReaderWriter i o i
Put :: o -> FReaderWriter i o ()
type IT i o a = FFree (FReaderWriter i o) a
instance Functor (FFree f) where
fmap = undefined
instance Applicative (FFree f) where
pure = undefined
(<*>) = undefined
instance Monad (FFree f) where
return = Pure
Pure a >>= k = k a
Impure fx k' >>= k = Impure fx (k' >=> k)
data Lan (g :: * -> * ) a where
FMap :: (x -> a) -> g x -> Lan g a
type FFRee g = Free (Lan g)
data Union (r :: [* -> * ]) x where
class Member t r where
inj :: t v -> Union r v
prj :: Union r v -> Maybe (t v)
decomp :: Union (t ': r) v -> Either (Union r v) (t v)
decomp = undefined
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment