Re: [Haskell-cafe] "import" functionality in DSLs

2011-04-16 Thread Nikhil A. Patil
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
> >

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] "import" functionality in DSLs

2011-04-16 Thread Luke Palmer
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 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
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Platform 2011.2.0.1 now available

2011-04-16 Thread Don Stewart
On Fri, Apr 15, 2011 at 11:50 PM, Joachim Breitner  wrote:
> Hi,
>
> Am Freitag, den 15.04.2011, 15:44 -0700 schrieb Don Stewart:
>> We're pleased to announce the 2011.2.0.1 release of the Haskell Platform:
>> a single, standard Haskell distribution for everyone.
>>
>> Download the Haskell Platform 2011.2.0.1:
>>
>>     http://haskell.org/platform/
>
> or use Debian unstable, which ships this version of the platform since
> five days already: http://people.debian.org/~nomeata/platform.html


Good work!

Is the link to Debian on the http://haskell.org/platform homepage correct?


>  * We only ship it already because the file on
> http://code.galois.com/darcs/haskell-platform/haskell-platform.cabal
> has already changed earlier, which was linked by
> http://hackage.haskell.org/platform/changelog.html so we thought this is
> already official and released and we just missed the announcement.

Do you watch the haskell-platf...@projects.haskell.org mailing list?
There we announced the freeze, and the initial release candidates.


> Maybe it would be better if released versions get their own, static
> directory again, as it was the case for
> http://hackage.haskell.org/platform/2010.1.0.0/haskell-platform.cabal
> and
> http://hackage.haskell.org/platform/2010.2.0.0/haskell-platform.cabal

Good idea.

> and the relationship between the repositories
> http://code.haskell.org/haskell-platform/ and
> http://code.galois.com/darcs/haskell-platform/ should be explained on
> http://trac.haskell.org/haskell-platform/.

That's just a temporary problem, since code.haskell.org was moved.

-- Don

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cairo and Haskell

2011-04-16 Thread Hans van Thiel
Hello Paulo,

<< I guess that would be using Cairo so I can have a 2d canvas to draw
in and maybe even preview before exporting to PDF. However, I can't find
any documentation on Cairo with Haskell or any code examples related to
what I want to do. >>

With regard to export to pdf and other formats this might be useful:
http://muitovar.com/gtk2hs/app1.html (There's a Spanish translation
too.) However, this tutorial is a few years old now, and I don't know if
it's still up to date for the later Gtk2Hs versions.

Best Regards,

Hans van Thiel



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] "import" functionality in DSLs

2011-04-16 Thread Nikhil A. Patil
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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] "import" functionality in DSLs

2011-04-16 Thread Felipe Almeida Lessa
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.

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.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] "import" functionality in DSLs

2011-04-16 Thread 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


Re: [Haskell-cafe] 64 bit generic link warning on every compile

2011-04-16 Thread Ozgur Akgun
"The -read_only_relocs flag is no longer used on OS X 64, which eliminates
some warnings."

http://www.haskell.org/ghc/docs/7.0.3/html/users_guide/release-7-0-3.html

HTH,
Ozgur

On 16 April 2011 03:47, Andrew Pennebaker wrote:

> GHC 7 compiles fine, but there's an additional warning during linking.
>
> $ system_profiler SPSoftwareDataType | grep "System Version"
>   System Version: Mac OS X 10.6.7 (10J869)
> $ ghc --version
> The Glorious Glasgow Haskell Compilation System, version 7.0.2
> $ cat hello.hs
> #!/usr/bin/env runhaskell
>
> module Main where
>
> main :: IO ()
> main = putStrLn "Hello World"
> $ ghc --make hello.hs
> [1 of 1] Compiling Main ( hello.hs, hello.o )
> Linking hello ...
> ld: warning: -read_only_relocs cannot be used with x86_64
> $ ./hello
> Hello World
>
> Cheers,
>
> Andrew Pennebaker
> www.yellosoft.us
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>


-- 
Ozgur Akgun
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe