Safe Haskell | None |
---|---|
Language | Haskell98 |
- data Set n :: [*] -> * where
- get :: Var v -> State `[v :-> (a :! R)]` a
- put :: Var v -> a -> State `[v :-> (a :! W)]` ()
- data State s a = State {}
- data k :-> v :: Symbol -> * -> * = (Var k) :-> v
- data a :! s = a :! (Action s)
- data Eff
- data Action s = Eff
- data Var k :: Symbol -> * where
- union :: Unionable s t => Set s -> Set t -> Set (UnionS s t)
- type UnionS s t = Nub (Sort (Append s t))
- type family Reads t
- type family Writes t
- type Unionable s t = (Sortable (Append s t), Nubable (Sort (Append s t)) (Nub (Sort (Append s t))), Split s t (Union s t))
- class Sortable xs
- type SetLike s = Nub (Sort s)
- type StateSet f = (StateSetProperties f, StateSetProperties (Reads f), StateSetProperties (Writes f))
- type IntersectR s t = (Sortable (Append s t), Update (Sort (Append s t)) t)
- class Update s t
- type family Sort xs :: [k]
- class Split s t st
Documentation
data Set n :: [*] -> * where
get :: Var v -> State `[v :-> (a :! R)]` a Source
Read from a variable v
of type a
. Raise a read effect.
put :: Var v -> a -> State `[v :-> (a :! W)]` () Source
Write to a variable v
with a value of type a
. Raises a write effect
Parametric effect state monad
Effect [*] State | |
type Unit [*] State = [] * | |
type Plus [*] State s t = UnionS s t | |
type Inv [*] State s t = (IsSet * s, IsSet * (Reads s), IsSet * (Writes s), IsSet * t, IsSet * (Reads t), IsSet * (Writes t), (~) [*] (Reads (Reads t)) (Reads t), (~) [*] (Writes (Writes s)) (Writes s), Split (Reads s) (Reads t) (Reads (UnionS s t)), Unionable (Writes s) (Writes t), IntersectR (Writes s) (Reads t), (~) [*] (Writes (UnionS s t)) (UnionS (Writes s) (Writes t))) |
data k :-> v :: Symbol -> * -> *
(Show (Var k), Show v) => Show ((:->) k v) | |
(Monoid u, Nubable ((:) * ((:->) k u) s)) => Nubable ((:) * ((:->) k u) ((:) * ((:->) k u) s)) | Define the operation for removing duplicates using mappend |
Update ((:) * ((:->) u ((:!) b s)) as) as' => Update ((:) * ((:->) v ((:!) a W)) ((:) * ((:->) u ((:!) b s)) as)) as' | |
Update ((:) * ((:->) v ((:!) a R)) as) as' => Update ((:) * ((:->) v ((:!) a W)) ((:) * ((:->) v ((:!) b R)) as)) as' | |
Update ((:) * ((:->) u ((:!) b s)) as) as' => Update ((:) * ((:->) v ((:!) a R)) ((:) * ((:->) u ((:!) b s)) as)) ((:) * ((:->) v ((:!) a R)) as') | |
type Cmp * ((:->) v a) ((:->) u b) = CmpSymbol v u |
Describes an effect action s
on a value of type a
(Show (Action f), Show a) => Show ((:!) a f) | |
Update ((:) * ((:->) u ((:!) b s)) as) as' => Update ((:) * ((:->) v ((:!) a W)) ((:) * ((:->) u ((:!) b s)) as)) as' | |
Update ((:) * ((:->) v ((:!) a R)) as) as' => Update ((:) * ((:->) v ((:!) a W)) ((:) * ((:->) v ((:!) b R)) as)) as' | |
Update ((:) * ((:->) u ((:!) b s)) as) as' => Update ((:) * ((:->) v ((:!) a R)) ((:) * ((:->) u ((:!) b s)) as)) ((:) * ((:->) v ((:!) a R)) as') |
Provides an effect-parameterised version of the state monad, which gives an effect system for stateful computations with annotations that are sets of variable-type-action triples.
Distinguish reads, writes, and read-writes
Provides a wrapper for effect actions
union :: Unionable s t => Set s -> Set t -> Set (UnionS s t) Source
Union operation for state effects
Calculate just the reader effects
Calculate just the writer effects
type Unionable s t = (Sortable (Append s t), Nubable (Sort (Append s t)) (Nub (Sort (Append s t))), Split s t (Union s t)) Source
class Sortable xs
quicksort
type StateSet f = (StateSetProperties f, StateSetProperties (Reads f), StateSetProperties (Writes f)) Source
Captures what it means to be a set of state effects
type IntersectR s t = (Sortable (Append s t), Update (Sort (Append s t)) t) Source
Update reads, that is any writes are pushed into reads, a bit like intersection
update
Update xs ([] *) | |
Update ((:) * ((:->) u ((:!) b s)) as) as' => Update ((:) * ((:->) v ((:!) a W)) ((:) * ((:->) u ((:!) b s)) as)) as' | |
Update ((:) * ((:->) v ((:!) a R)) as) as' => Update ((:) * ((:->) v ((:!) a W)) ((:) * ((:->) v ((:!) b R)) as)) as' | |
Update ((:) * e ([] *)) ((:) * e ([] *)) | |
Update ((:) * ((:->) u ((:!) b s)) as) as' => Update ((:) * ((:->) v ((:!) a R)) ((:) * ((:->) u ((:!) b s)) as)) ((:) * ((:->) v ((:!) a R)) as') |
type family Sort xs :: [k]