THEff-0.1.0.1: TH implementation of effects.

Safe HaskellNone
LanguageHaskell2010
Extensions
  • FlexibleContexts
  • KindSignatures
  • RankNTypes
  • ExplicitForAll

Control.THEff.Exception

Contents

Synopsis

Overview

{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}

import Control.THEff
import Control.THEff.Exception
 
mkEff "MyException" ''Except    ''String   ''NoEff

safeSqrt :: Float -> Eff (MyException m Float) Float
safeSqrt x =  do
    throwIf (x<0) "The argument must be non-negative."
    return $ sqrt x 
>>> runMyException id $ safeSqrt 4
Right 2.0
>>> runMyException id $ safeSqrt (-1)
Left "The argument must be non-negative." 

Types and functions used in mkEff

data Except' v e Source

Actually, the effect type - v - Type - the parameter of the effect. - e - mkEff generated type.

data Except m e o v a Source

Type implements link in the chain of effects. Constructors must be named {EffectName}{Outer|WriterAction|WriterResult} and have a specified types of fields. - m - Or Monad (if use the Lift) or phantom type - stub (if used NoEff). - o - Type of outer effect. - a - The result of mkEff generated runEEEE... function.

Constructors

ExceptOuter (o m e) 
ExceptAction (Except' v e) 
ExceptResult a 

type ExceptArgT v = v -> v Source

Type of fourth argument of runEffExcept and first argument of runEEEE.

type ExceptResT r v = Either v r Source

Result type of runEEEE.

effExcept :: EffClass Except' v e => Except' v r -> Eff e r Source

This function is used in the mkEff generated runEEEE functions and typically in effect action functions. Calling the effect action.

runEffExcept Source

Arguments

:: forall (t :: * -> *) (u :: (* -> *) -> * -> *) (m :: * -> *) (m1 :: * -> *) (o :: (* -> *) -> * -> *). Monad m 
=> (u t r -> (r -> m (ExceptResT z v)) -> m (ExceptResT z v))

The outer effect function

-> (Except m1 e o w a -> r)

The chain of effects link wrapper.

-> (r -> Except t r u v z)

The chain of effects link unwrapper.

-> ExceptArgT v

The argument of effect. Except value map. Usualy id.

-> Eff r a 
-> m (ExceptResT z v) 

The main function of the effect implementing. This function is used in the mkEff generated runEEEE functions.

Functions that use this effect

throwExc :: EffClass Except' v e => v -> Eff e () Source

Throw effect specific exception.

throwIf :: EffClass Except' v e => Bool -> v -> Eff e () Source

Throw effect specific exception if first argument is True.