Difference between revisions of "LGtk/Semantics"

From HaskellWiki
Jump to navigation Jump to search
m
(add motivation)
Line 37: Line 37:
 
== References ==
 
== References ==
   
  +
=== Motivation ===
It is convenient to use lenses with the state monad
 
([http://www.haskellforall.com/2013/05/program-imperatively-using-haskell.html see this use case]) and the reader monad.
 
   
  +
Let <hask>s :: *</hask> be a type.
Let's call a value with type <hask>Lens s a</hask> a '''reference''' of the state monad <hask>State s</hask> and the reader monad <hask>Reader s</hask>.
 
   
  +
Consider the three types <hask>Lens s :: * -> *</hask>, <hask>State s :: * -> *</hask>, <hask>Reader s :: * -> *</hask> with their type class instances and operations.
References are distinguished from lenses, because we would like to make the program state <hask>s</hask> unaccessible to guarantee linear use of the state for example.
 
   
 
This structure is useful in practice ([http://www.haskellforall.com/2013/05/program-imperatively-using-haskell.html see this use case]). We have the following goals:
There are several ways to model references in Haskell.
 
  +
LGtk models them as type classes with associated types, but that is just a technical detail.
 
  +
* Define a structure similar to <hask>(Lens s, State s, Reader s)</hask> in which <hask>s</hask> is not accessable.
  +
* Extend the defined structure with operations which help modularity.
  +
  +
The first goal is justified by our solution for the second goal. The second goal is justified by the fact that a global state is not easy to maintain explicitly.
   
 
=== Types ===
 
=== Types ===
  +
  +
We keep the types <hask>(Lens s, State s, Reader s)</hask> but give them a more restricted API. There are several ways to do this in Haskell. LGtk defines type classes with associated types, but that is just a technical detail.
   
 
Instead of giving a concrete implementation in Haskell, suppose that
 
Instead of giving a concrete implementation in Haskell, suppose that
   
* <hask>s</hask> is a fixed type,
+
* <hask>s</hask> is a fixed arbitrary type,
* <hask>Ref :: * -> *</hask> ~ <hask>Lens s</hask>, references are lenses from <hask>s</hask> to the type of the referred value,
+
* <hask>Ref :: * -> *</hask> ~ <hask>Lens s</hask>; '''references''' are lenses from <hask>s</hask> to the type of the referred value,
* <hask>R :: * -> *</hask> ~ <hask>Reader s</hask>, the '''reference reading monad''' is the reader monad over <hask>s</hask>,
+
* <hask>R :: * -> *</hask> ~ <hask>Reader s</hask>; the '''reference reading monad''' is the reader monad over <hask>s</hask>,
* <hask>S :: * -> *</hask> ~ <hask>State s</hask>, the '''reference reading and writing monad''' is the state monad over <hask>s</hask>.
+
* <hask>S :: * -> *</hask> ~ <hask>State s</hask>; the '''reference modifying monad''' is the state monad over <hask>s</hask>.
   
The three equality constraints are not exposed in the API.
+
The three equality constraints are not exposed in the API, of course.
   
 
=== Operations ===
 
=== Operations ===
   
Exposed operations of <hask>Ref</hask>, <hask>S</hask> and <hask>R</hask>:
+
Exposed operations of <hask>Ref</hask>, <hask>S</hask> and <hask>R</hask> are the following:
   
* The <hask>Monad</hask> instance of <hask>S</hask> and <hask>R</hask>
+
* The <hask>Monad</hask> instance of <hask>R</hask> and <hask>S</hask>
   
 
* The monad morphism between <hask>R</hask> and <hask>S</hask>
 
* The monad morphism between <hask>R</hask> and <hask>S</hask>

Revision as of 17:30, 2 June 2013

The semantics of LGtk is given by a reference implementation. The reference implementation is given in three stages: lenses, references and effects.

Lenses

LGtk use simple lenses defined in the data-lens package:

newtype Lens a b = Lens { runLens :: a -> Store b a }

This data type is isomorphic to (a -> b, b -> a -> a), the well-know lens data type. The isomorphism is established by the following operations:

getL :: Lens a b -> a -> b
setL :: Lens a b -> b -> a -> a
lens :: (a -> b) -> (b -> a -> a) -> Lens a b

Lens laws

The three well-known laws for lenses:

  • get-set: set k (get k a) a === a
  • set-get: get k (set k b a) === b
  • set-set: set k b2 (set k b1 a) === set k b2 a

Impure lenses, i.e. lenses which brake lens laws are allowed in certain places. Those places are explicitly marked and explained in this overview.

References

Motivation

Let s :: * be a type.

Consider the three types Lens s :: * -> *, State s :: * -> *, Reader s :: * -> * with their type class instances and operations.

This structure is useful in practice (see this use case). We have the following goals:

  • Define a structure similar to (Lens s, State s, Reader s) in which s is not accessable.
  • Extend the defined structure with operations which help modularity.

The first goal is justified by our solution for the second goal. The second goal is justified by the fact that a global state is not easy to maintain explicitly.

Types

We keep the types (Lens s, State s, Reader s) but give them a more restricted API. There are several ways to do this in Haskell. LGtk defines type classes with associated types, but that is just a technical detail.

Instead of giving a concrete implementation in Haskell, suppose that

  • s is a fixed arbitrary type,
  • Ref :: * -> * ~ Lens s; references are lenses from s to the type of the referred value,
  • R :: * -> * ~ Reader s; the reference reading monad is the reader monad over s,
  • S :: * -> * ~ State s; the reference modifying monad is the state monad over s.

The three equality constraints are not exposed in the API, of course.

Operations

Exposed operations of Ref, S and R are the following:

  • The Monad instance of R and S
  • The monad morphism between R and S
liftReadPart :: R a -> S a
liftReadPart = gets . runReader
  • Reference read
readRef :: Ref a -> R a
readRef = reader . getL
  • Reference write
writeRef :: Ref a -> a -> S ()
writeRef = modify . setL r
  • Lens application on a reference
lensMap :: Lens a b -> Ref a -> Ref b
lensMap = (.)
  • Reference join
joinRef :: R (Ref a) -> Ref a
joinRef = Lens . join . (runLens .) . runReader
  • The unit reference
unitRef :: Ref ()
unitRef = lens (const ()) (const id)

Note that the identity lens is not a reference because that would leak the program state s.

Reference creation

There should be a possibility for new reference creation too.

New reference creation with a given initial value extends the state. For example, if the state is (1, 'c') :: (Int, Char), extending the state with True :: Bool would yield the state ((1, 'c'), True) :: ((Int, Char), Bool).

We could model the type change of the state with an indexed monad, but that would complicate both the API and the implementation too.

Instead of changing the type of the state, we use an extensible state, a data type S with the operations

empty :: S
extend :: a -> State S (Lens S a)

such that the following laws hold:

  • extend v >> return () === return ()
  • extend v >>= liftReadPart . readRef === return v

The first law sais that extend has no side-effect, i.e. extending the state does not change the values of existing references. The second law sais that extending the state with value v creates a reference with inital value v.

Is there a state with a well-behaved extend function?

The answer is yes, but we should guarantee linear usage of the state. This is great, because linear usage is guaranteed with the restricted API!

How can such an S be implemented? And how can such an S be implemented efficiently? These questions are not relevant for the semantics, but there is an efficient implementation with IORefs.

Reference creation API

Let S be an extensible state as specified before. Let s = S in the definition of references.

  • C :: (* -> *) -> * -> * ~ StateT S, the reference creating monad is the state monad transformer over S.

The equality constraint is not exposed in the API. The following functions are exposed:

  • New reference creation
newRef :: Monad m => a -> C m (Ref a)
newRef v = mapStateT (return . runIdentity) $ extend v
  • Lift reference read and write operations
liftWrite :: Monad m => S a -> C m a
liftWrite = mapStateT (return . runIdentity)
  • Derived MonadTrans instance of C to be able to lift operations in the m monad.

Note that C is parameterized by a monad because in this way it is easier to add other effects later.

Running

The API is completed with the following function:

  • Run the reference creation monad
runC :: Monad m => C m a -> m a
runC x = runStateT x empty

Lens-stacks

TODO

Effects

TODO