"import" functionality in DSLs

Hi, I am planning a simple monadic DSL (frankly, calling it a DSL is a bit of a stretch; it's just a somewhat glorified state monad), and I wish to implement some kind of "import" functionality for it. The DSL code looks something like this:
doit :: DSL Term doit = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" -- begin beautiful DSL code let x = k + n0 return $ x + x
The code above adds identifiers "+", "0", "k" to the DSL monad and conveniently exposes haskell identifiers (+), n0, k for the user to use in code that follows. (Note that these define_* functions make state updates in the underlying state monad.) Needless to say, most functions like doit have very similar define_* calls in the beginning. Thus, I want to implement some kind of import functionality. Ideally, the code would look like this:
module DSLPrelude where
prelude :: DSL () prelude = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" return ()
module Main where import DSLPrelude
doit :: DSL Term doit = do prelude -- begin beautiful DSL code let x = k + n0 return $ x + x
...but of course that won't work since (+), n0, k are not in scope. I can think of two solutions, both of which I dislike: Solution 1:
module DSLPrelude where
prelude :: DSL (Term -> Term -> Term, Term, Term) prelude = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" return ((+), n0, k)
module Main where import DSLPrelude
doit :: DSL Term doit = do ((+), k, n0) <- prelude -- begin beautiful DSL code let x = k + n0 return $ x + x
This is quite unsafe: I have mistakenly swapped k and n0 in doit, without failing typecheck. Solution 2:
module DSLPrelude where
(+) :: DSL (Term -> Term -> Term) n0 :: DSL Term k :: DSL Term (+) = define_function "+" 2 n0 = define_constant "0" k = define_constant "k"
module Main where import DSLPrelude
doit :: DSL Term doit = do (+) <- (+) n0 <- n0 k <- k -- begin beautiful DSL code let x = k + n0 return $ x + x
...which works, but still has quite a bit of boilerplate crap. I feel this would be a common problem with a lot of DSLs, so I am curious to know how others solve it. Any pointers and suggestions are most welcome and greatly appreciated. Thanks! nikhil

On Sat, Apr 16, 2011 at 10:29 AM, Nikhil A. Patil
doit :: DSL Term doit = do (+) <- (+) n0 <- n0 k <- k -- begin beautiful DSL code let x = k + n0 return $ x + x
I guess the core problem is that on each time you say '(+) <- (+)', you may actually get something different depending on what 'define_function' does. You say yourself that these functions change a hidden state. So, without any internal changes, I doubt you could do something better. One possible solution may be to have a special case for your Prelude functions and constants that never change. That is, if currently you have data Term = Term Key ... type Key = Integer and you store other informations about each term on your hidden state, then you may use data Term = Term Key ... data Key = Prelude Integer | User Integer Your define_* functions always return User keys, however now you can have unsafe versions of them that take a key as argument. Then your Prelude would be
module DSLPrelude where
(+) :: Term -> Term -> Term n0 :: Term k :: Term (+) = unsafe_define_function t1 "+" 2 n0 = unsafe_define_constant t2 "0" k = unsafe_define_constant t3 "k"
t1, t2, t3 :: Key (t1:t2:t3:_) = map Prelude [1..]
Of course, this is a lot of handwaving, but you haven't provided any details about your internal implementation. HTH, -- Felipe.

On Sat, Apr 16, 2011 at 08:55 CDT, Felipe Almeida Lessa wrote:
On Sat, Apr 16, 2011 at 10:29 AM, Nikhil A. Patil
wrote: doit :: DSL Term doit = do (+) <- (+) n0 <- n0 k <- k -- begin beautiful DSL code let x = k + n0 return $ x + x
I guess the core problem is that on each time you say '(+) <- (+)', you may actually get something different depending on what 'define_function' does. You say yourself that these functions change a hidden state. So, without any internal changes, I doubt you could do something better.
Thanks very much for your response! You are right, I haven't defined the semantics of this operation in my post. For the example in my post, the define_* functions are idempotent on the hidden state, when used with the same arguments (i.e. the multiple calls are redundant). I explicitly handle this in the implementation of the DSL monad: basically, there is a Set that tracks what functions have been previously defined, and when a conflicting re-definition is found, I throw a run-time error. But: how can I get rid of the boilerplate code, and give the user the appearance that she is "import"-ing identifier bindings from another file? nikhil
One possible solution may be to have a special case for your Prelude functions and constants that never change. That is, if currently you have
data Term = Term Key ... type Key = Integer
and you store other informations about each term on your hidden state, then you may use
data Term = Term Key ... data Key = Prelude Integer | User Integer
Your define_* functions always return User keys, however now you can have unsafe versions of them that take a key as argument. Then your Prelude would be
module DSLPrelude where
(+) :: Term -> Term -> Term n0 :: Term k :: Term (+) = unsafe_define_function t1 "+" 2 n0 = unsafe_define_constant t2 "0" k = unsafe_define_constant t3 "k"
t1, t2, t3 :: Key (t1:t2:t3:_) = map Prelude [1..]
Of course, this is a lot of handwaving, but you haven't provided any details about your internal implementation.
HTH,
-- Felipe.

On 4/16/11 9:55 AM, Felipe Almeida Lessa wrote:
On Sat, Apr 16, 2011 at 10:29 AM, Nikhil A. Patil
wrote: doit :: DSL Term doit = do (+)<- (+) n0<- n0 k<- k -- begin beautiful DSL code let x = k + n0 return $ x + x
I guess the core problem is that on each time you say '(+)<- (+)', you may actually get something different depending on what 'define_function' does. You say yourself that these functions change a hidden state. So, without any internal changes, I doubt you could do something better.
That really depends. For example, first assume we've hoisted things out: module DSLPrelude where import qualified Prelude (+) = define_function (Prelude.+) 2 ... Now, rather than having the define_* functions perform side effects themselves, instead we could have the generated (+) register itself in the state the first time it's called in each DSL, assuming the DSL has (or can have) a way to keep a log of which things it has used (i.e., could run when executed). This also has the benefit that the DSL can prune out definitions that are unused, and collapse any duplicate definitions it detects. Of course, the downside is that it means (+) is monadic now, which may get in the way of your beautiful DSL code. Whether it's worth it or not depends on what the DSL is for. If it's pseudo-assembly, then it should be fine; if it aims to be more of a high-level mathematical notation, then not so much. Though Luke's -XRecordWildCards approach was my first thought. -- Live well, ~wren

You can get away with this using {-# LANGUAGE RecordWildCards #-}, if you
put your prelude into a record. Here's a test I did to make sure the
technique worked:
{-# LANGUAGE RecordWildCards #-}
import Prelude hiding ((+))
data Foo = Foo {
(+) :: Int -> Int -> Int,
n0 :: Int
}
prelude :: IO Foo
prelude = return $ Foo { (+) = (*), n0 = 1 }
doit :: IO Int
doit = do
Foo{..} <- prelude
return $ n0 + 3 + 4
ghci> doit
12
On Sat, Apr 16, 2011 at 7:29 AM, Nikhil A. Patil
Hi,
I am planning a simple monadic DSL (frankly, calling it a DSL is a bit of a stretch; it's just a somewhat glorified state monad), and I wish to implement some kind of "import" functionality for it.
The DSL code looks something like this:
doit :: DSL Term doit = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" -- begin beautiful DSL code let x = k + n0 return $ x + x
The code above adds identifiers "+", "0", "k" to the DSL monad and conveniently exposes haskell identifiers (+), n0, k for the user to use in code that follows. (Note that these define_* functions make state updates in the underlying state monad.)
Needless to say, most functions like doit have very similar define_* calls in the beginning. Thus, I want to implement some kind of import functionality. Ideally, the code would look like this:
module DSLPrelude where
prelude :: DSL () prelude = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" return ()
module Main where import DSLPrelude
doit :: DSL Term doit = do prelude -- begin beautiful DSL code let x = k + n0 return $ x + x
...but of course that won't work since (+), n0, k are not in scope.
I can think of two solutions, both of which I dislike:
Solution 1:
module DSLPrelude where
prelude :: DSL (Term -> Term -> Term, Term, Term) prelude = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" return ((+), n0, k)
module Main where import DSLPrelude
doit :: DSL Term doit = do ((+), k, n0) <- prelude -- begin beautiful DSL code let x = k + n0 return $ x + x
This is quite unsafe: I have mistakenly swapped k and n0 in doit, without failing typecheck.
Solution 2:
module DSLPrelude where
(+) :: DSL (Term -> Term -> Term) n0 :: DSL Term k :: DSL Term (+) = define_function "+" 2 n0 = define_constant "0" k = define_constant "k"
module Main where import DSLPrelude
doit :: DSL Term doit = do (+) <- (+) n0 <- n0 k <- k -- begin beautiful DSL code let x = k + n0 return $ x + x
...which works, but still has quite a bit of boilerplate crap.
I feel this would be a common problem with a lot of DSLs, so I am curious to know how others solve it. Any pointers and suggestions are most welcome and greatly appreciated.
Thanks!
nikhil
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Apr 16, 2011 at 13:49 CDT, Luke Palmer wrote:
You can get away with this using {-# LANGUAGE RecordWildCards #-}, if you put your prelude into a record. Here's a test I did to make sure the technique worked:
{-# LANGUAGE RecordWildCards #-}
import Prelude hiding ((+))
data Foo = Foo { (+) :: Int -> Int -> Int, n0 :: Int }
prelude :: IO Foo prelude = return $ Foo { (+) = (*), n0 = 1 }
doit :: IO Int doit = do Foo{..} <- prelude return $ n0 + 3 + 4
Oh, that's pretty sweet! Thank you very much! :) nikhil
ghci> doit 12
On Sat, Apr 16, 2011 at 7:29 AM, Nikhil A. Patil
wrote: Hi,
I am planning a simple monadic DSL (frankly, calling it a DSL is a bit of a stretch; it's just a somewhat glorified state monad), and I wish to implement some kind of "import" functionality for it.
The DSL code looks something like this:
doit :: DSL Term doit = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" -- begin beautiful DSL code let x = k + n0 return $ x + x
The code above adds identifiers "+", "0", "k" to the DSL monad and conveniently exposes haskell identifiers (+), n0, k for the user to use in code that follows. (Note that these define_* functions make state updates in the underlying state monad.)
Needless to say, most functions like doit have very similar define_* calls in the beginning. Thus, I want to implement some kind of import functionality. Ideally, the code would look like this:
module DSLPrelude where
prelude :: DSL () prelude = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" return ()
module Main where import DSLPrelude
doit :: DSL Term doit = do prelude -- begin beautiful DSL code let x = k + n0 return $ x + x
...but of course that won't work since (+), n0, k are not in scope.
I can think of two solutions, both of which I dislike:
Solution 1:
module DSLPrelude where
prelude :: DSL (Term -> Term -> Term, Term, Term) prelude = do (+) <- define_function "+" 2 n0 <- define_constant "0" k <- define_constant "k" return ((+), n0, k)
module Main where import DSLPrelude
doit :: DSL Term doit = do ((+), k, n0) <- prelude -- begin beautiful DSL code let x = k + n0 return $ x + x
This is quite unsafe: I have mistakenly swapped k and n0 in doit, without failing typecheck.
Solution 2:
module DSLPrelude where
(+) :: DSL (Term -> Term -> Term) n0 :: DSL Term k :: DSL Term (+) = define_function "+" 2 n0 = define_constant "0" k = define_constant "k"
module Main where import DSLPrelude
doit :: DSL Term doit = do (+) <- (+) n0 <- n0 k <- k -- begin beautiful DSL code let x = k + n0 return $ x + x
...which works, but still has quite a bit of boilerplate crap.
I feel this would be a common problem with a lot of DSLs, so I am curious to know how others solve it. Any pointers and suggestions are most welcome and greatly appreciated.
Thanks!
nikhil
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
Felipe Almeida Lessa
-
Luke Palmer
-
Nikhil A. Patil
-
wren ng thornton