ixmonad-0.57: Embeds effect systems into Haskell using parameteric effect monads

Safe HaskellNone
LanguageHaskell98

Control.Effect.Writer

Synopsis

Documentation

data Writer w a Source

Provides an effect-parameterised version of the writer monad. Effects are sets of variable-type pairs, providing an effect system for writer effects.

Constructors

Writer 

Fields

runWriter :: (a, Set w)
 

Instances

Effect [*] Writer 
Superset s t => Subeffect [*] Writer s t 
type Unit [*] Writer = [] * 
type Plus [*] Writer s t = Union s t 
type Inv [*] Writer s t = (IsSet s, IsSet t, Unionable s t) 

data Symbol :: *

(Kind) This is the kind of type-level symbols.

Instances

type (==) Symbol a b = EqSymbol a b 

put :: Var v -> a -> Writer `[v :-> a]` () Source

Write to variable v with value of type a

data k :-> v infixl 2 Source

Instances

(Show (Var k), Show v) => Show ((:->) k v) 
Chooser (CmpSymbol j k) => OrdH ((:->) j u) ((:->) k v) 
(Monoid u, Nubable ((:) * ((:->) k u) s)) => Nubable ((:) * ((:->) k u) ((:) * ((:->) k u) s))

Define the operation for removing duplicates using mappend

Update ((:) * ((:->) j ((:!) b s)) as) as' => Update ((:) * ((:->) k ((:!) a W)) ((:) * ((:->) j ((:!) b s)) as)) as' 
Update ((:) * ((:->) k ((:!) a R)) as) as' => Update ((:) * ((:->) k ((:!) a W)) ((:) * ((:->) k ((:!) b R)) as)) as' 
Update ((:) * ((:->) k ((:!) b R)) as) as' => Update ((:) * ((:->) k ((:!) a s)) ((:) * ((:->) k ((:!) b s)) as)) as' 
Update ((:) * ((:->) j ((:!) b s)) as) as' => Update ((:) * ((:->) k ((:!) a R)) ((:) * ((:->) j ((:!) b s)) as)) ((:) * ((:->) k ((:!) a R)) as') 
type Max ((:->) j u) ((:->) k v) = (:->) (Select Symbol j k k j) (Select * j k v u) 
type Min ((:->) j u) ((:->) k v) = (:->) (Select Symbol j k j k) (Select * j k u v) 

type IsSet s = s ~ Nub (Sort s) Source

data Set n where Source

Constructors

Empty :: Set [] 
Ext :: e -> Set s -> Set (e : s) 

Instances

(Show e, Show' (Set s)) => Show (Set ((:) * e s)) 
Show (Set ([] *)) 

union :: Unionable s t => Set s -> Set t -> Set (Union s t) Source

data Var k where Source

Constructors

Var :: Var k 
X :: Var "x" 
Y :: Var "y" 
Z :: Var "z" 

Instances

Show (Var "x") 
Show (Var "y") 
Show (Var "z") 

type Union s t = Nub (Sort (Append s t)) Source

type Unionable s t = (Sortable (Append s t), Nubable (Sort (Append s t))) Source