io-effects-0.1.0: Taming the IO monad

Safe HaskellNone
LanguageHaskell2010

IO.Effects

Contents

Synopsis

Welcome!

Welcome to io-effects, a light-weight yet high performance effect library with the aim of taming the IO monad. The IO monad is the workhorse of any Haskell program - the entry point of our program is main :: IO (), and there is no way to "leave" IO once you're there. However, the IO monad has a huge amount of power - it can open files, perform network requests, and - as they saying goes - launch the missiles. All of these are important functions, but as our programs grow it becomes increasingly difficult to reason about what IO is being performed. For example, asking the question "does this program access my database?" is a difficult question to answer - with only IO, we have no option other than reading all of the source code.

Enter io-effects. Programs written using io-effects are just like the IO programs we're familiar with, but exactly what IO is being performed is explicitly described in the types of our programs. A program that has access to a database may have a type such as Member Database es => Program es a. In fact, if es is truly polymorphic, this program can do nothing but access a database. These constraints can be combined as well, so a program with the type ( Member Database es, Member HTTP es ) => Program es a is a program that may access a database or may make HTTP requests.

Defining Effects

To define an effect, we need to write three things:

  1. A GADT for the signature of our effect. This is a list of all possible methods.
  2. Helper functions to define your effects DSL.
  3. One or more intpreretations of your effect.

We will consider this with the familiar example an effect that provides input and output against the terminal.

First, our effect signature:

data Teletype m a where
  ReadLine :: Teletype m String
  WriteLine :: String -> Teletype m ()

Next, some helper functions to provide a nicer API to users of our effect:

readLine :: Member Teletype es => Program es String
readLine = send ReadLine

writeLine :: Member Teletype es => String -> Program es ()
writeLine = send . WriteLine

Finally, we need to provide an interpretation for this effect. In this example, we will reinterpret the Teletype effect into general IO:

teletypeToIO
  :: Member ( Lift IO ) es
  => ProgramWithHandler Teletype es a
  -> Program es a
teletypeToIO =
  interpret \case
    ReadLine -> liftIO getLine
    WriteLine l -> liftIO ( putStrLn l )

And that's it! With this, we can now write some basic programs:

greeter :: Member Teletype es => Program es ()
greeter = do
  writeLine "Hello! What is your name?"
  name <- readLine
  writeLine ( "Hi, " ++ name ++ " - thanks for trying out io-effects!" )

main :: IO ()
main =
  programToIO ( teletypeToIO greeter )

The Core of io-effects

data Program (es :: [(* -> *) -> * -> *]) a Source #

The Program monad is where you will type your effectful programs. The parameter es is an effect list - the list of all possible effects that your program has access to.

When writing computations in the Program monad, you should keep es polymorphic and add constraints using the Member type class. For example, prefer:

myApp :: Member HTTP es => Program es a

over

myApp :: Program ( HTTP : es ) a

as the former is much more composable.

Instances
Monad (Program es) Source # 
Instance details

Defined in IO.Effects.Internal

Methods

(>>=) :: Program es a -> (a -> Program es b) -> Program es b #

(>>) :: Program es a -> Program es b -> Program es b #

return :: a -> Program es a #

fail :: String -> Program es a #

Functor (Program es) Source # 
Instance details

Defined in IO.Effects.Internal

Methods

fmap :: (a -> b) -> Program es a -> Program es b #

(<$) :: a -> Program es b -> Program es a #

Applicative (Program es) Source # 
Instance details

Defined in IO.Effects.Internal

Methods

pure :: a -> Program es a #

(<*>) :: Program es (a -> b) -> Program es a -> Program es b #

liftA2 :: (a -> b -> c) -> Program es a -> Program es b -> Program es c #

(*>) :: Program es a -> Program es b -> Program es b #

(<*) :: Program es a -> Program es b -> Program es a #

Member (Lift IO :: (Type -> Type) -> Type -> Type) es => MonadIO (Program es) Source # 
Instance details

Defined in IO.Effects.Lift

Methods

liftIO :: IO a -> Program es a #

programToIO :: Program es a -> IO a Source #

Any Program can be reduced at any time to IO, at which point all in scope handlers will be used to provide interpretations to the effects in es.

interpret Source #

Arguments

:: Effect e 
=> (forall x. e (Program es) x -> Program es x)

This function pattern matches on the effect signature e, and interprets each individual effect method into a program with access to the effects in the effect list es.

-> ProgramWithHandler e es a

The program to supply this interpretation to.

-> Program es a 

You provide an interpretation of an individual effect using interpret.

class Member e es where Source #

The Member e es constraint witnesses that the effect e can be found in the effect list es.

Methods

send :: e (Program es) a -> Program es a Source #

Send a single effect method call into a Program.

Instances
(Effect e, Member e es) => Member e (f ': es) Source # 
Instance details

Defined in IO.Effects.Internal

Methods

send :: e (Program (f ': es)) a -> Program (f ': es) a Source #

(Effect e, HandlerInScope s e es) => Member e (Handled e s ': es) Source # 
Instance details

Defined in IO.Effects.Internal

Methods

send :: e (Program (Handled e s ': es)) a -> Program (Handled e s ': es) a Source #

Other Types

type ProgramWithHandler e es a = forall s. HandlerInScope s e es => Program (Handled e s ': es) a Source #

A ProgramWithHandler e es computation similar to a normal Program ( e : es) computation, but with the added information that an effect handler for e is in scope.

You will typically not write programs with this type, but you will use it whenever you provide an interpretation using interpret.

data Handled e s m a Source #

A Handled effect has the same capabilities as the effect e, but this provides evidence to GHC that an effect handler for this effect is in scope.

Instances
(Effect e, HandlerInScope s e es) => Member e (Handled e s ': es) Source # 
Instance details

Defined in IO.Effects.Internal

Methods

send :: e (Program (Handled e s ': es)) a -> Program (Handled e s ': es) a Source #