[Haskell-cafe] manage effects in a DSL

oleg at okmij.org oleg at okmij.org
Fri Jan 31 08:24:50 UTC 2014


> - What do you mean by "The type Cont Int a describes an impure computation,
> which may abort with an Int value, for example".
> Aborting with an Int value is akin to exceptions?

I see that using Cont monad wasn't a good idea. The point can be made
simply, with an Error monad or applicative. Here is a simple function
to multiply a list of integers:

> muls :: [Integer] -> Either e Integer
> muls []    = pure 1
> muls (h:t) = (h*) <$> muls t

We give the signature (which the compiler accepts) with the
polymorphic return type Either e Integer, fully polymorphic over
e. Therefore, muls throws no exceptions.

Here is a bit more optimized function, which stops all multiplications
once zero is encountered.

> mulse :: [Integer] -> Either Integer Integer
> mulse []    = pure 1
> mulse (0:t) = Left 0
> mulse (h:t) = (h*) <$> mulse t

We cannot make the return type (Either e Integer), it must be
(Either Integer Integer). The function can indeed throw an exception.

If we handle the exception

> muls' :: [Integer] -> Either e Integer
> muls' l = either pure pure $ mulse l

the effect is encapsulated and the type is polymorphic again.

> - for me it's not clear when to choose an "applicative" or a "monadic" DSL?
> Betsides, what's the rational behind the name "let_" (never seen it before)?

The first rule of thumb is to use the simplest structure that does the
job. Another good rule is to distinguish the DSL from its
implementation. For example, the DSL below
        http://okmij.org/ftp/tagless-final/index.html#call-by-any
has no monads. It is a simple lambda-calculus with constants. Its
implementation in Haskell, the embedding, does use monads, sometimes quite
specific monads (e.g., IO, to print the trace of evaluation). But these
monads are not exposed to the DSL programmer. That article also shows
off let_.

    > data Eff = Effect | NoEffect
    > -- first type parameter is used to track effects
    > data Exp :: Eff -> * -> * where
    >   ReadAccount  :: Exp r Int  --ReadAccount can be used in whatever
    >   monad (with or without effect)
    >   WriteAccount :: Exp NoEffect Int -> Exp Effect ()  --WriteAccount
    >   takes an effect-less expression, and returns an effectfull expression

This is exactly what I had in mind (and probably Jacques as well).

> Other pointers where this idiom is realised??
Lots of places; ST monad comes to mind, and the Region monad. This
trick is often used to track, for example, information flow security
(the label then reflects the sensitivity level of data processed by
the computation, Low or High). See, for example,

        http://www.cse.chalmers.se/~russo/seclib.htm
        http://www.scs.stanford.edu/~deian/pubs/stefan:2011:flexible-slides.pdf

or just search for information flow control or information flow
security in Haskell. Edward Yang has a lot to say on this topic.




More information about the Haskell-Cafe mailing list