Multiple Interpretations for a monad?

Hi everyone, in my attempts to remove boilerplate and thus to do more "abstraction" I come across a number of interesting things and suggestions. Especially blog posts from Dan Piponi and also Heinrich Apfelmus. I think what they both are saying is that you can construct / implement some sort of 2 layered monad which can then have more than one interpretation. In the responses to one of my posts on DSLs Dan Piponi also points out that he considers monads also to be DSLs. It didn't click with me when he said it, but reading more of his blog posts made me remember that. Now I know this is probably something obvious to most haskellers, but to me it's not. Did I understand this correctly so far? Günther

Monads aren't necessarily EDSLs by themselves but are often shipped with
functions that provide what would make them an EDSL. Take the State monad,
it has at least a get and a put function to work with the state in the
monad. That get and put are commands that function only within the domain
of the State monad, and therefore could be thought of as an embedded
language that is used to work with the state encapsulated in the State Monad
computation.
The way I like to think of it, a Monad provides an environment or a context
within which it is very convenient to express an EDSL, and that this style
of coding should be encouraged! :-)
Dave
2010/2/25 Günther Schmidt
Hi everyone,
in my attempts to remove boilerplate and thus to do more "abstraction" I come across a number of interesting things and suggestions.
Especially blog posts from Dan Piponi and also Heinrich Apfelmus. I think what they both are saying is that you can construct / implement some sort of 2 layered monad which can then have more than one interpretation.
In the responses to one of my posts on DSLs Dan Piponi also points out that he considers monads also to be DSLs. It didn't click with me when he said it, but reading more of his blog posts made me remember that.
Now I know this is probably something obvious to most haskellers, but to me it's not.
Did I understand this correctly so far?
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

To take this a step further, there is the DSL:
get :: m S
put :: S -> m ()
and the concrete implementation
m = State S
Of course, there are other monads which implement this DSL as well:
m = StateT S IO
m = Prompt StatePrompt
with
data StatePrompt a where
Get :: StatePrompt S
Put :: S -> StatePrompt ()
The "Prompt" solution(1) encodes your program (object of type Prompt
StatePrompt a) into a way such that it can be used with *any*
interpreter, whether it is the (s -> (a,s)) of State, or lifted into
part of some larger DSL, or whatever. For example, to lift into
StateT S IO:
interpretPrompt :: Prompt StatePrompt a -> StateT S IO a
interpretPrompt = runPromptM f where
f :: StatePrompt a -> StateT S IO a
f Get = get
f (Put x) = put x
So, I think a better way to describe it is that a DSL could be
implemented by many monads, and some monads let you interpret the DSL
into another monad. Even StateT is this way, in a sense; you
interpret it with runStateT:
runStateT myProgram initialState :: IO (S, a)
Now you have another program in a different monad (IO) which you need
to interpret somehow.
-- ryan
(1) http://hackage.haskell.org/package/MonadPrompt
2010/2/25 David Leimbach
Monads aren't necessarily EDSLs by themselves but are often shipped with functions that provide what would make them an EDSL. Take the State monad, it has at least a get and a put function to work with the state in the monad. That get and put are commands that function only within the domain of the State monad, and therefore could be thought of as an embedded language that is used to work with the state encapsulated in the State Monad computation. The way I like to think of it, a Monad provides an environment or a context within which it is very convenient to express an EDSL, and that this style of coding should be encouraged! :-) Dave 2010/2/25 Günther Schmidt
Hi everyone,
in my attempts to remove boilerplate and thus to do more "abstraction" I come across a number of interesting things and suggestions.
Especially blog posts from Dan Piponi and also Heinrich Apfelmus. I think what they both are saying is that you can construct / implement some sort of 2 layered monad which can then have more than one interpretation.
In the responses to one of my posts on DSLs Dan Piponi also points out that he considers monads also to be DSLs. It didn't click with me when he said it, but reading more of his blog posts made me remember that.
Now I know this is probably something obvious to most haskellers, but to me it's not.
Did I understand this correctly so far?
Günther
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Ryan Ingram wrote:
To take this a step further, there is the DSL:
get :: m S put :: S -> m ()
and the concrete implementation
m = State S
Of course, there are other monads which implement this DSL as well:
m = StateT S IO
m = Prompt StatePrompt with data StatePrompt a where Get :: StatePrompt S Put :: S -> StatePrompt ()
Elaborating on that, the DSL consists of two specific functions get, put and two general function (>>=), return Every combination of those is a program in the DSL. Example programs: get >>= put get >>= \x -> return (x,x) put 1 >>= \() -> get >>= \x -> return (2*x) This is the *syntactic* part of the DSL. Of course, we also need *semantics*, and those are given by an interpreter function. Examples: interpret :: m a -> (S -> a) interpret :: m a -> (S -> (a,S)) interpret :: m a -> StateT S IO a When the state monad is implemented as m a = S -> (a,S) this function is just the identity interpret :: (S -> (a,S)) -> (S -> (a,S)) interpret = id but as the MonadPrompt or operational packages show, this does not need to be the case; it is, in fact, beneficial to use a generic representation for the syntax and make the interpret function do all the work. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com
participants (4)
-
David Leimbach
-
Günther Schmidt
-
Heinrich Apfelmus
-
Ryan Ingram