Re: [Haskell-cafe] adding recursion to a DSL

2013-02-19 Thread Emil Axelsson
You probably don't need recursion in the DSL for this (that would 
require a way to detect cycles in the expressions). For this example, it 
looks like all you need is to add something like `map` as a DSL construct.


Your example could perhaps be expressed as

  forEach (1,1000) (\n - out (matrixMult, A, n, row, matrix-row))

For this you need a way to reify functions in the DSL. For an example of 
how to do this, see the `While` and `Arr` constructs in this paper:


  http://www.cse.chalmers.se/~emax/documents/svenningsson2013combining.pdf

I'm not familiar with your particular DSL though, so I might have missed 
something.


/ Emil

2013-02-17 23:53, frit...@joerg.cc skrev:

I have a tiny DSL that actually works quite well. When I say

import language.CWMWL

main = runCWMWL $ do
 out (matrixMult, A, 1, row, matrix-row)

then runCWMWL is a function that is exported by language.CWMWL. This parses the 
experession and takes some action.

Now, A is the name of the matrix and the third tuple element would represent the numbe of 
the row. For example 1 to 1. I want to achieve some sort of elegant 
(means readable code, a good representation) recursion that would let me do something like
sequence [ out (matrixMult, A, n, row, matrix-row) | n - [1..1000] ]
but in a nicer manner an without expending this to 1 lines of code at 
compile time.

How can I best introduce recursion into my DSL or borrow this from the host language 
Haskell effectively?

--Joerg



___
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] Maintaining lambdabot

2013-02-19 Thread Jan Stolarek
I'm happy to hear your approval. 

I've spent some time yesterday cleaning up the code and writing down all things 
that do not work. 
The list I made is avaliable on github:

https://github.com/killy/lambdabot/issues

There are 17 open issues at the moment and I know I will not have enough time 
to resolve all of 
them on my own. There are a few blockers, so the current code is definitely not 
yet suitable for 
any kind of release.

With all that said I would appreciate help of the community :-) There's a lot 
to do and the tasks 
vary in difficulty: from updating documentation and fixing unused imports to 
fixing exceptions. 
If anyone is willing to help please contact me via email or comments on github.

Janek

P.S. The development is done in the 'upstream' branch

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


Re: [Haskell-cafe] adding recursion to a DSL

2013-02-19 Thread Edsko de Vries
Hi Joerg,

You might find Abstract Syntax Graphs for Domain Specific Languages by
Bruno Oliveira and Andres Löh (
http://ropas.snu.ac.kr/~bruno/papers/ASGDSL.pdf) a helpful reference to
adding things like recursion (and other binding constructs) to your DSL.

Edsko


On Tue, Feb 19, 2013 at 9:47 AM, Emil Axelsson e...@chalmers.se wrote:

 You probably don't need recursion in the DSL for this (that would require
 a way to detect cycles in the expressions). For this example, it looks like
 all you need is to add something like `map` as a DSL construct.

 Your example could perhaps be expressed as

   forEach (1,1000) (\n - out (matrixMult, A, n, row, matrix-row))

 For this you need a way to reify functions in the DSL. For an example of
 how to do this, see the `While` and `Arr` constructs in this paper:

   http://www.cse.chalmers.se/~**emax/documents/**
 svenningsson2013combining.pdfhttp://www.cse.chalmers.se/~emax/documents/svenningsson2013combining.pdf

 I'm not familiar with your particular DSL though, so I might have missed
 something.

 / Emil

 2013-02-17 23:53, frit...@joerg.cc skrev:

 I have a tiny DSL that actually works quite well. When I say

 import language.CWMWL

 main = runCWMWL $ do
  out (matrixMult, A, 1, row, matrix-row)

 then runCWMWL is a function that is exported by language.CWMWL. This
 parses the experession and takes some action.

 Now, A is the name of the matrix and the third tuple element would
 represent the numbe of the row. For example 1 to 1. I want to achieve
 some sort of elegant (means readable code, a good representation)
 recursion that would let me do something like
 sequence [ out (matrixMult, A, n, row, matrix-row) | n - [1..1000] ]
 but in a nicer manner an without expending this to 1 lines of code at
 compile time.

 How can I best introduce recursion into my DSL or borrow this from the
 host language Haskell effectively?

 --Joerg



 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


[Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Anton Kholomiov
I'm glad to announce the package for Common subexpression elimination [1].
It's an implementation of the hashconsig algorithm as described in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most generic
way.
You can define the AST for your DSL as fixpoint type[2]. And then all you
need
to use the library is to define the instance for type class `Traversable`.
This idea is inspired by `data-reify` [3] package which you can use to
transform
your ASTs to DAGs too. But it relies on inspection of the references for
values
when `data-fix-cse` doesn't sacrifices the purity.

A short example:

Let's define a tiny DSL for signals

import Data.Fix

type Name = String

type E = Fix Exp

data Exp a = Const Double | ReadPort Name | Tfm Name [a] | Mix a a
  deriving (Show, Eq, Ord)

We can make constant signals, read them from some ports and transform them
(apply some named function to the list of signals) and mix two signals.

Let's define an instance of the Traversable (hence for the Functor and
Foldable)

import Control.Applicative

import Data.Monoid
import Data.Traversable
import Data.Foldable

instance Functor Exp where
  fmap f x = case x of
 Const d - Const d
 ReadPort n - ReadPort n
 Mix a b - Mix (f a) (f b)
 Tfm n as - Tfm n $ fmap f as

instance Foldable Exp where
  foldMap f x = case x of
 Mix a b - f a  f b
 Tfm n as - mconcat $ fmap f as
 _ - mempty

instance Traversable Exp where
   traverse f x = case x of
  Mix a b - Mix $ f a * f b
  Tfm n as - Tfm n $ traverse f as
  a - pure a

Now we can use the functio `cse`

cse :: 
(Eqhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Eq.html#t:Eq(f
Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
Ordhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Ord.html#t:Ord(f
Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
Traversablehttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Traversable.html#t:Traversablef)
=
Fixhttp://hackage.haskell.org/packages/archive/data-fix/0.0.1/doc/html/Data-Fix.html#t:Fixf
-
Daghttp://hackage.haskell.org/packages/archive/data-fix-cse/0.0.1/doc/html/Data-Fix-Cse.html#t:Dagf

to transform our AST to DAG. DAG is already sorted.

Later we can define a handy wrapper to hide the details from the client

newtype Sig = Sig { unSig :: E }

You can find examples in the package archive

Extra-Source-Files:
test/Exp.hs
test/Impl.hs
test/Expl.hs

If you want to see a real world example of usage you can find it
in the csound-expression[4]. An edsl for the Csound language.

One side-note form my experience: Fixpoint types can be very flexible.
It's easy to compose them. If suddenly we need to add some extra data
to all cases from the example above we can easily do it with just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.

[1] http://hackage.haskell.org/package/data-fix-cse-0.0.1
[2] http://hackage.haskell.org/package/data-fix-0.0.1
[3] http://hackage.haskell.org/package/data-reify
[4] http://hackage.haskell.org/package/csound-expression


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


Re: [Haskell-cafe] FunPtr to C function with #arguments determined atruntime?

2013-02-19 Thread Ertugrul Söylemez
Ryan Newton rrnew...@gmail.com wrote:

 My problem is that I can't create a type representing what I want at
 the Haskell type-check time, and I need such a type for either
 casting or a foreign import.  For example, let's say the function
 takes a number of Int arguments between 1 and 1000.  If I find out at
 runtime that I need a function with 613 Int arguments, I would need
 to create the type (Int - Int ... - IO ()) to cast to.  I suppose
 there may be some way to create such a dependent type with
 Typeable/Data.Dynamic, since it's monomorphic. Or in theory you could
 dynamically generate new Haskell code to create the type
 (System.Eval.Haskell)...

Simpler.  This is our goal:

main :: IO ()
main = withFunction (push 3 $ push 4 $ done)

The withFunction function constructs a function at run-time, say, by
reading a file, yet this is completely type-safe, statically checked
code and also looks quite nice.

First make a clear separation between the producer and consumer of a
type.  The producer constructs the type, the consumer uses it.  Then you
can use either existentials or higher-rank types.  Let's say the user
enters a number, and we want to treat it as Integer if possible,
otherwise as Double.  This is the traditional approach:

withNum :: String - b - (Integer - b) - (Double - b) - b
withNum str none ki kd
| [(x, _)] - reads str = ki x
| [(x, _)] - reads str = kd x
| otherwise = none

Here is an improved variant:

withNum :: String - b - (forall a. (Num a) = a - b) - b
withNum str none k
| [(x, _)] - reads str = k (x :: Integer)
| [(x, _)] - reads str = k (x :: Double)
| otherwise = none

This is almost the same function, but with an important difference.  For
both cases the same continuation is called, because withNum accepts only
functions that can promise to work for all numeric types.  In other
words, the function must be polymorphic enough.  What really happens
here is that I determine the type at run-time depending on the string.
That's how lightweight dependent types work.  Meet withFunction from the
teaser.  It reveals only its type signature for now:

withFunction ::
(forall a. (Push a) = a - IO b)
- IO b

The withFunction function lifts something from value level and
constructs a function of the correct type from it.  Whatever the
continuation receives is a function of the proper type.  However, you
can't just call the function yet, because withFunction's argument
promises that it works for every type 'a'.  So it can't just pass it an
Int.  That's where the Push class comes in.  Here is a very simple,
non-fancy Int-only way to define it:

class Push a where
push :: Int - (forall b. (Push b) = b - IO c) - a - IO c
done :: a - IO ()

instance (Push a) = Push (Int - a) where
push x k f = k (f x)
done _ = throwIO (userError Messed up my arguments, sorry)

instance Push (IO ()) where
push _ _ _ = throwIO (userError Messed up my arguments, sorry)
done = id

Don't worry about the scary types.  They are actually pretty simple:
The push function, if possible, applies the given Int (first argument)
to the given function (third argument).  It passes the result to the
continuation (second argument), which again promises to work for every
Push.  For non-functions a run-time exception is raised (obviously you
can't do that at compile time, so this is the best we can get).  Here is
an example withFunction together with its application:

withFunction k =
let f :: Int - Int - IO ()
f x y = print x  print y
in k f

main :: IO ()
main = withFunction (push 3 $ push 4 $ done)

Ain't that nice?

Of course the FunPtr is now implicit in whatever withFunction constructs
it from.  While you still need the foreign declaration you now get
type-safety for types determined at run-time.  If the constructed
function takes another Int argument, push is the way to apply it.

I hope this helps.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] Subject: ANNOUNCE: grid-3.0.1 (tile maps for board games or maths)

2013-02-19 Thread Amy de Buitléir
Twan van Laarhoven twanvl at gmail.com writes:

 After taking a peek at the documentation: have you considered removing
 the size function from Grid?
. . .
 It might also be useful to add a rectangular grid type where diagonally 
 adjacent cells are also neighbors.
. . .
 Another interesting idea is to have modifier types that change which 
 cells are neighbors, for example you could have

Those are all great suggestions, thank you. I'll look into incorporating
them into the next major release.


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


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Emil Axelsson

2013-02-19 12:10, Anton Kholomiov skrev:

I'm glad to announce the package for Commonsubexpression elimination [1].
It's an implementation of the hashconsig algorithm as described in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most
generic way.
You can define the AST for your DSL as fixpoint type[2]. And then all
you need
to use the library is to define the instance for type class `Traversable`.


One way to make the library even more useful would have been to base it 
on compdata instead of data-fix. Compdata has support for composable 
types and lots of extra functionality. On the other hand, it's easy 
enough to translate from compdata terms to your `Fix`...





One side-note form my experience: Fixpoint types can be very flexible.
It's easy to compose them. If suddenly we need to add some extra data
to all cases from the example above we can easily do it with just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.


Very useful indeed! A more principled way to extend data types in this 
way is Data Types à la Carte:


  http://dx.doi.org/10.1017/S0956796808006758

(Implemented in compdata.)

/ Emil


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


Re: [Haskell-cafe] layers: A prototypical 2d platform game

2013-02-19 Thread Henk-Jan van Tuyl
On Mon, 18 Feb 2013 18:48:01 +0100, Daniel Trstenjak  
daniel.trsten...@gmail.com wrote:




Hi all,

also if there's not that much to see and only a few minutes of gameplay,
but after spending quite a few hours writing it, getting a feeling for
Haskell and it's usage, perhaps it's in some way useful for someone,
even if just for a few minutes of distraction.

https://github.com/dan-t/layers


Greetings,
Daniel


It seems to me that there is something missing from this e-mail.

Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

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


Re: [Haskell-cafe] layers: A prototypical 2d platform game

2013-02-19 Thread Daniel Trstenjak

Hi Henk-Jan,

 It seems to me that there is something missing from this e-mail.

What are you missing?


Greetings,
Daniel

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


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Anton Kholomiov
There are several packages that already define fixpoints (another one is
about unification), but all packages that I'm aware of define a lot of
functionality
that I don't need (and actually don't understand, packages with fixpoint
types
tend to be rather dense with math). I'd like it to be simple and
lightweight.
Just fixpoints, just folds and unfolds.


2013/2/19 Emil Axelsson e...@chalmers.se

 2013-02-19 12:10, Anton Kholomiov skrev:

 I'm glad to announce the package for Commonsubexpression elimination [1].

 It's an implementation of the hashconsig algorithm as described in the
 paper
 'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
 Kiselyov.

 Main point of the library is to define this algorithm in the most
 generic way.
 You can define the AST for your DSL as fixpoint type[2]. And then all
 you need
 to use the library is to define the instance for type class `Traversable`.


 One way to make the library even more useful would have been to base it on
 compdata instead of data-fix. Compdata has support for composable types and
 lots of extra functionality. On the other hand, it's easy enough to
 translate from compdata terms to your `Fix`...




  One side-note form my experience: Fixpoint types can be very flexible.
 It's easy to compose them. If suddenly we need to add some extra data
 to all cases from the example above we can easily do it with just another
 Functor:

 Imagine that we want to use a SampleRate value with all signals.
 Then we can do it like this:

 type E = Fix SampledExp

 data SampledExp a = SampledExp SampleRate (Exp a)

 then we should define an instance of the type class Traversable
 for our new type SampleRate. The Exp doesn't change.


 Very useful indeed! A more principled way to extend data types in this way
 is Data Types à la Carte:

   
 http://dx.doi.org/10.1017/**S0956796808006758http://dx.doi.org/10.1017/S0956796808006758

 (Implemented in compdata.)

 / Emil


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


Re: [Haskell-cafe] layers: A prototypical 2d platform game

2013-02-19 Thread Vo Minh Thu
2013/2/19 Daniel Trstenjak daniel.trsten...@gmail.com:

 Hi Henk-Jan,

 It seems to me that there is something missing from this e-mail.

 What are you missing?

Screenshots obviously ;)

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


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Emil Axelsson
Fully understandable! Compdata would be quite a heavy dependency for 
your library.


I'm just generally fond of the idea of collecting all DSL implementation 
tricks under one umbrella. That requires using the same term representation.


/ Emil

2013-02-19 14:12, Anton Kholomiov skrev:

There are several packages that already define fixpoints (another one is
about unification), but all packages that I'm aware of define a lot of
functionality
that I don't need (and actually don't understand, packages with fixpoint
types
tend to be rather dense with math). I'd like it to be simple and
lightweight.
Just fixpoints, just folds and unfolds.


2013/2/19 Emil Axelsson e...@chalmers.se mailto:e...@chalmers.se

2013-02-19 12:10, Anton Kholomiov skrev:

I'm glad to announce the package for Commonsubexpression
elimination [1].

It's an implementation of the hashconsig algorithm as described
in the
paper
'Implementing Explicit and Finding Implicit Sharing in EDSLs' by
Oleg
Kiselyov.

Main point of the library is to define this algorithm in the most
generic way.
You can define the AST for your DSL as fixpoint type[2]. And
then all
you need
to use the library is to define the instance for type class
`Traversable`.


One way to make the library even more useful would have been to base
it on compdata instead of data-fix. Compdata has support for
composable types and lots of extra functionality. On the other hand,
it's easy enough to translate from compdata terms to your `Fix`...




One side-note form my experience: Fixpoint types can be very
flexible.
It's easy to compose them. If suddenly we need to add some extra
data
to all cases from the example above we can easily do it with
just another
Functor:

Imagine that we want to use a SampleRate value with all signals.
Then we can do it like this:

type E = Fix SampledExp

data SampledExp a = SampledExp SampleRate (Exp a)

then we should define an instance of the type class Traversable
for our new type SampleRate. The Exp doesn't change.


Very useful indeed! A more principled way to extend data types in
this way is Data Types à la Carte:

http://dx.doi.org/10.1017/__S0956796808006758
http://dx.doi.org/10.1017/S0956796808006758

(Implemented in compdata.)

/ Emil




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


Re: [Haskell-cafe] layers: A prototypical 2d platform game

2013-02-19 Thread Daniel Trstenjak

On Tue, Feb 19, 2013 at 02:15:33PM +0100, Vo Minh Thu wrote:
 Screenshots obviously ;)

Hurray!
attachment: layers.png___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] layers: A prototypical 2d platform game

2013-02-19 Thread Mateusz Kowalczyk
On 19/02/13 13:39, Daniel Trstenjak wrote:
 
 On Tue, Feb 19, 2013 at 02:15:33PM +0100, Vo Minh Thu wrote:
 Screenshots obviously ;)
 
 Hurray!
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

Eh, I expected a game where we get to catch combinators and other cool
stuff.

How about a game where you collect functions that compose with each
other and you lose points on those that don't. The implementation might
be tricky but I think it's a nice spin-off from the typical formula.

-- 
Mateusz K.

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


[Haskell-cafe] What is a Haskell way to implement flags?

2013-02-19 Thread Branimir Maksimovic

In C usual way is to set some bit in integer variable by shifting or oring,and 
than check flag integer variable by anding with particular flag value.What is 
Haskell way?
Thanks.   ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What is a Haskell way to implement flags?

2013-02-19 Thread mukesh tiwari
The same as C way. You can import Data.Bits and can use the functions.

Prelude import Data.Bits
Prelude Data.Bits Data.Bits.
Data.Bits...   Data.Bits.bitDefault   Data.Bits.complementBit
Data.Bits.rotate   Data.Bits.shift
Data.Bits.testBitDefault
Data.Bits..|.Data.Bits.bitSize  Data.Bits.isSigned
Data.Bits.rotateL  Data.Bits.shiftL   Data.Bits.unsafeShiftL
Data.Bits.BitsData.Bits.clearBit Data.Bits.popCount
Data.Bits.rotateR  Data.Bits.shiftR   Data.Bits.unsafeShiftR
Data.Bits.bit  Data.Bits.complement
Data.Bits.popCountDefault  Data.Bits.setBit
Data.Bits.testBit  Data.Bits.xor
Prelude Data.Bits (..) 1 2
0
Prelude Data.Bits (..) 2 2
2


I wrote a minimum spanning tree code and rather than maintaining the list
of visited nodes, I took a Integer  because of arbitrary precision and set
the bits  accordingly.

visited :: Int - Integer - ( Bool , Integer )
visited x vis = ( t == 0 , vis' ) where
t = ( B... ) ( B.shiftL ( 1 :: Integer ) x ) vis
vis' = ( B..|. ) ( B.shiftL ( 1 :: Integer ) x ) vis


Mukesh



On Tue, Feb 19, 2013 at 8:41 PM, Branimir Maksimovic bm...@hotmail.comwrote:

  In C usual way is to set some bit in integer variable by shifting or
 oring,
 and than check flag integer variable by anding with particular flag value.
 What is Haskell way?

 Thanks.


 ___
 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] Maintaining lambdabot

2013-02-19 Thread James Cook
For what it's worth, I also have a fork of lambdabot[1] I've been using for 
quite a while now, which may provide a cleaner starting point.  In particular, 
it updates the plugin and command API to be (IMO) quite a bit cleaner and 
easier to use and understand.  It could probably use some attention to security 
in the eval module (I've relaxed it quite a bit because I only run it on a 
private IRC server), but it also includes a lot of fixes and updates to other 
modules.

[1] https://github.com/mokus0/lambdabot


On Feb 19, 2013, at 2:00 AM, Jan Stolarek jan.stola...@p.lodz.pl wrote:

 I'm happy to hear your approval. 
 
 I've spent some time yesterday cleaning up the code and writing down all 
 things that do not work. 
 The list I made is avaliable on github:
 
 https://github.com/killy/lambdabot/issues
 
 There are 17 open issues at the moment and I know I will not have enough time 
 to resolve all of 
 them on my own. There are a few blockers, so the current code is definitely 
 not yet suitable for 
 any kind of release.
 
 With all that said I would appreciate help of the community :-) There's a lot 
 to do and the tasks 
 vary in difficulty: from updating documentation and fixing unused imports to 
 fixing exceptions. 
 If anyone is willing to help please contact me via email or comments on 
 github.
 
 Janek
 
 P.S. The development is done in the 'upstream' branch
 
 ___
 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] What is a Haskell way to implement flags?

2013-02-19 Thread Donn Cave
Quoth Branimir Maksimovic bm...@hotmail.com,
  In C usual way is to set some bit in integer variable by shifting or oring,
 and than check flag integer variable by anding with particular flag value.
 What is Haskell way?

Of course you may do the very same thing, if you like.  I think if
there's only one of these for the entire program, most Haskell programmers
would use a Boolean value, as the space you save with a single bit
is of too little consequence to bother with bit twiddling in Haskell.
The various flags that belong together might be housed in a `record'.

Or, in some contexts a list of an algebraic type might be useful -
like,  if elem FlagDebug flags, or
   if any (flip elem flags) [FlagDebug, FlagVerbose]

Donn

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


Re: [Haskell-cafe] What is a Haskell way to implement flags?

2013-02-19 Thread Brandon Allbery
On Tue, Feb 19, 2013 at 10:11 AM, Branimir Maksimovic bm...@hotmail.comwrote:

  In C usual way is to set some bit in integer variable by shifting or
 oring,
 and than check flag integer variable by anding with particular flag value.
 What is Haskell way?


You can do that, but a somewhat more idiomatic way would be a list (or,
slightly less conveniently but more accurately, a Data.Set) of constructors
from a flags ADT.

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] layers: A prototypical 2d platform game

2013-02-19 Thread Henk-Jan van Tuyl
On Tue, 19 Feb 2013 13:55:14 +0100, Daniel Trstenjak  
daniel.trsten...@gmail.com wrote:




Hi Henk-Jan,


It seems to me that there is something missing from this e-mail.


What are you missing?


The message starts with the word also, so it looks if there should be  
some other text in front of it.


Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

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


Re: [Haskell-cafe] Free lunch with GADTs

2013-02-19 Thread Mark Flamer
Tristan, Please let me know how this works out for you. I was struggling with
something similar over the last few days. It's expressed in these 2 S.O.
questions. In my case I'm going to probably just move on and stick with a
standard ADT for now. It was interesting to explore the possibilities
though.  

http://stackoverflow.com/questions/14949021/return-type-as-a-result-of-term-or-value-calculation

http://stackoverflow.com/questions/14918867/trouble-with-datakinds



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Free-lunch-with-GADTs-tp5725865p5726160.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-19 Thread Jan Stolarek
Wow, this indeed looks like a nice starting point, though I can't build 
lambdabot from your repo - 
seems that dice package is not on Hackage. Is this the package that you rely on:

https://github.com/serialhex/dice ?

Anyway, how would you feel about changes that I would like to make:
- move all modules into Lambdabot. namespace
- remove unlambda, brainfuck and show from the repo. They are on hackage, no 
need to keep them 
here - these packages aren't even used in the build process.
- cleanup scripts
- add package versions to cabal file

This is mostly code refactoring.

Janek

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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-19 Thread James Cook
Sorry, I uploaded it this morning since I knew it wasn't there (it's the dice 
repo from my github account, mokus0).  Have you run cabal update in the last 
4 or 5 hours?

On Feb 19, 2013, at 2:36 PM, Jan Stolarek jan.stola...@p.lodz.pl wrote:

 Wow, this indeed looks like a nice starting point, though I can't build 
 lambdabot from your repo - 
 seems that dice package is not on Hackage. Is this the package that you rely 
 on:
 
 https://github.com/serialhex/dice ?
 
 Anyway, how would you feel about changes that I would like to make:
 - move all modules into Lambdabot. namespace
 - remove unlambda, brainfuck and show from the repo. They are on hackage, no 
 need to keep them 
 here - these packages aren't even used in the build process.
 - cleanup scripts
 - add package versions to cabal file
 
 This is mostly code refactoring.
 
 Janek
 


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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-19 Thread Gwern Branwen
On Tue, Feb 19, 2013 at 5:36 PM, Jan Stolarek jan.stola...@p.lodz.pl wrote:
 - remove unlambda, brainfuck and show from the repo. They are on hackage, no 
 need to keep them
 here - these packages aren't even used in the build process.

Where will they go?

-- 
gwern
http://www.gwern.net

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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-19 Thread James Cook
On Feb 19, 2013, at 2:36 PM, Jan Stolarek jan.stola...@p.lodz.pl wrote:

 Anyway, how would you feel about changes that I would like to make:
 - move all modules into Lambdabot. namespace
 - remove unlambda, brainfuck and show from the repo. They are on hackage, no 
 need to keep them 
 here - these packages aren't even used in the build process.
 - cleanup scripts
 - add package versions to cabal file

I have no objections to any of these, though I would recommend as Gwern hinted 
that if related packages are to be removed that they should also be given new 
homes - I believe that the lambdabot source is currently the main home of these 
packages.

I tend to prefer not to give package version upper bounds, but that's more of a 
preference than an objection ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parsec without data declarations/AST

2013-02-19 Thread Sean Cormican
I have been trying to create a parser for a functional programming
language, but there is no need to create an AST but merely check that the
code is valid according to the grammar.

In the following tutorial I have been trying to take some pointers from,
data declarations are used to create an AST for the language, There is, as
I understand a way to parse the language without an AST.

http://www.haskell.org/haskellwiki/Parsing_a_simple_imperative_language

My question is what should the type signatures for example parseFile
function instead of Stmt accept as input if the parser is to accept
Strings and numerical expressions alike ?

Thanks for any help,
Seán
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec without data declarations/AST

2013-02-19 Thread Alexander Solla
If all you want to do is check that the code is valid (i.e., you aren't
going to interpret the code), you can just return a Bool.  If you want to
interpret it, but don't want to have a Stmt type, you can return IO ()
actions.  In that case, the parser's type will be

Parser (IO ())

I think an algebraic AST (or even a functorial/monadic one) will help
separate concerns, and will eventually help when it comes time to optimize
your compiler.  It really isn't as much boilerplate as it looks like (in
fact, there's hardly any boilerplate if you target free monads and
interpret those in IO), and you get the type safety for which Haskell is
well-known.



On Tue, Feb 19, 2013 at 3:02 PM, Sean Cormican seancormic...@gmail.comwrote:

 I have been trying to create a parser for a functional programming
 language, but there is no need to create an AST but merely check that the
 code is valid according to the grammar.

 In the following tutorial I have been trying to take some pointers from,
 data declarations are used to create an AST for the language, There is, as
 I understand a way to parse the language without an AST.

 http://www.haskell.org/haskellwiki/Parsing_a_simple_imperative_language

 My question is what should the type signatures for example parseFile
 function instead of Stmt accept as input if the parser is to accept
 Strings and numerical expressions alike ?

 Thanks for any help,
 Seán

 ___
 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] Parsec without data declarations/AST

2013-02-19 Thread Alexander Solla
Come to think of it, a parsec parser already wraps over Either, so if all
you want to do is check if a result is valid, you can abuse the Either
semantics so that your type is:

Parser () -- the parser which returns nothing on success or an error on
failure.


On Tue, Feb 19, 2013 at 3:20 PM, Alexander Solla alex.so...@gmail.comwrote:

 If all you want to do is check that the code is valid (i.e., you aren't
 going to interpret the code), you can just return a Bool.  If you want to
 interpret it, but don't want to have a Stmt type, you can return IO ()
 actions.  In that case, the parser's type will be

 Parser (IO ())

 I think an algebraic AST (or even a functorial/monadic one) will help
 separate concerns, and will eventually help when it comes time to optimize
 your compiler.  It really isn't as much boilerplate as it looks like (in
 fact, there's hardly any boilerplate if you target free monads and
 interpret those in IO), and you get the type safety for which Haskell is
 well-known.



 On Tue, Feb 19, 2013 at 3:02 PM, Sean Cormican seancormic...@gmail.comwrote:

 I have been trying to create a parser for a functional programming
 language, but there is no need to create an AST but merely check that the
 code is valid according to the grammar.

 In the following tutorial I have been trying to take some pointers from,
 data declarations are used to create an AST for the language, There is, as
 I understand a way to parse the language without an AST.

 http://www.haskell.org/haskellwiki/Parsing_a_simple_imperative_language

 My question is what should the type signatures for example parseFile
 function instead of Stmt accept as input if the parser is to accept
 Strings and numerical expressions alike ?

 Thanks for any help,
 Seán

 ___
 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] What is a Haskell way to implement flags?

2013-02-19 Thread Ertugrul Söylemez
Brandon Allbery allber...@gmail.com wrote:

  In C usual way is to set some bit in integer variable by shifting or
  oring, and than check flag integer variable by anding with
  particular flag value. What is Haskell way?

 You can do that, but a somewhat more idiomatic way would be a list
 (or, slightly less conveniently but more accurately, a Data.Set) of
 constructors from a flags ADT.

The Set way is the one I would prefer.  In fact together with lenses you
even get the boolean interface and a nice interface in general.  Define
your option types:

data Flag =
Debug | Verbose
deriving (Ord)

data Options =
Options {
  _optFiles :: Set FilePath,
  _optFlags :: Set Flag
}

makeLenses ''Options

The fun starts when you have a state monad around Options, because then
you can use lenses very easily.  Let's add a file:

optFiles . contains blah.txt .= True

Let's set the Verbose flag:

optFlags . contains Verbose .= True

Let's flip the Verbose flag:

optFlags . contains Verbose %= not

Are we verbose?

verbose - use (optFlags . contains Verbose)

Have fun. =)


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


[Haskell-cafe] ANNOUNCE: smallcheck-1.0

2013-02-19 Thread Roman Cheplyaka
I am glad to announce a new major release of SmallCheck,
a property-based testing library for Haskell.

The major changes in this release are documented here:
http://ro-che.info/articles/2013-02-19-smallcheck.html

Roman

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


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Conal Elliott
What a delightfully elegant approach to CSE! I've been thinking about CSE
for DSELs and about functor fixpoints, but it never occurred to me to put
the two together.

Do you think the approach can be extended for non-regular (nested)
algebraic types (where the recursive data type is sometimes at a different
type instance)? For instance, it's very handy to use GADTs to capture
embedded language types in host language (Haskell) types, which leads to
non-regularity.

- Conal


On Tue, Feb 19, 2013 at 3:10 AM, Anton Kholomiov
anton.kholom...@gmail.comwrote:

 I'm glad to announce the package for Common subexpression elimination [1].

 It's an implementation of the hashconsig algorithm as described in the
 paper
 'Implementing Explicit and Finding Implicit Sharing in EDSLs' by Oleg
 Kiselyov.

 Main point of the library is to define this algorithm in the most generic
 way.
 You can define the AST for your DSL as fixpoint type[2]. And then all you
 need
 to use the library is to define the instance for type class `Traversable`.
 This idea is inspired by `data-reify` [3] package which you can use to
 transform
 your ASTs to DAGs too. But it relies on inspection of the references for
 values
 when `data-fix-cse` doesn't sacrifices the purity.

 A short example:

 Let's define a tiny DSL for signals

 import Data.Fix

 type Name = String

 type E = Fix Exp

 data Exp a = Const Double | ReadPort Name | Tfm Name [a] | Mix a a
   deriving (Show, Eq, Ord)

 We can make constant signals, read them from some ports and transform them
 (apply some named function to the list of signals) and mix two signals.

 Let's define an instance of the Traversable (hence for the Functor and
 Foldable)

 import Control.Applicative

 import Data.Monoid
 import Data.Traversable
 import Data.Foldable

 instance Functor Exp where
   fmap f x = case x of
  Const d - Const d
  ReadPort n - ReadPort n
  Mix a b - Mix (f a) (f b)
  Tfm n as - Tfm n $ fmap f as

 instance Foldable Exp where
   foldMap f x = case x of
  Mix a b - f a  f b
  Tfm n as - mconcat $ fmap f as
  _ - mempty

 instance Traversable Exp where
traverse f x = case x of
   Mix a b - Mix $ f a * f b
   Tfm n as - Tfm n $ traverse f as
   a - pure a

 Now we can use the functio `cse`

 cse :: 
 (Eqhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Eq.html#t:Eq(f
 Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
 Ordhttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Ord.html#t:Ord(f
 Inthttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Int.html#t:Int),
 Traversablehttp://hackage.haskell.org/packages/archive/base/4.6.0.1/doc/html/Data-Traversable.html#t:Traversablef)
  =
 Fixhttp://hackage.haskell.org/packages/archive/data-fix/0.0.1/doc/html/Data-Fix.html#t:Fixf
  -
 Daghttp://hackage.haskell.org/packages/archive/data-fix-cse/0.0.1/doc/html/Data-Fix-Cse.html#t:Dagf

 to transform our AST to DAG. DAG is already sorted.

 Later we can define a handy wrapper to hide the details from the client

 newtype Sig = Sig { unSig :: E }

 You can find examples in the package archive


 Extra-Source-Files:
 test/Exp.hs
 test/Impl.hs
 test/Expl.hs

 If you want to see a real world example of usage you can find it
 in the csound-expression[4]. An edsl for the Csound language.

 One side-note form my experience: Fixpoint types can be very flexible.
 It's easy to compose them. If suddenly we need to add some extra data
 to all cases from the example above we can easily do it with just another
 Functor:

 Imagine that we want to use a SampleRate value with all signals.
 Then we can do it like this:

 type E = Fix SampledExp

 data SampledExp a = SampledExp SampleRate (Exp a)

 then we should define an instance of the type class Traversable
 for our new type SampleRate. The Exp doesn't change.

 [1] http://hackage.haskell.org/package/data-fix-cse-0.0.1
 [2] http://hackage.haskell.org/package/data-fix-0.0.1
 [3] http://hackage.haskell.org/package/data-reify
 [4] http://hackage.haskell.org/package/csound-expression


 Anton

 ___
 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] generalized, tail-recursive left fold that can

2013-02-19 Thread oleg

  That said, to express foldl via foldr, we need a higher-order
  fold. There are various problems with higher-order folds, related to
  the cost of building closures. The problems are especially severe 
  in strict languages or strict contexts. Indeed,
  
  foldl_via_foldr f z l = foldr (\e a z - a (f z e)) id l z
  
  first constructs the closure and then applies it to z. The closure has
  the same structure as the list -- it is isomorphic to the
  list. However, the closure representation of a list takes typically
  quite more space than the list. So, in strict languages, expressing
  foldl via foldr is a really bad idea. It won't work for big lists.

 If we unroll foldr once (assuming l is not empty), we'll get

   \z - foldr (\e a z - a (f z e)) id (tail l) (f z (head l))

 which is a (shallow) closure. In order to observe what you describe (a
 closure isomorphic to the list) we'd need a language which does
 reductions inside closures.

I should've elaborated this point.

Let us consider monadic versions of foldr and foldl. First, monads,
sort of emulate strict contexts, making it easier to see when
closures are constructed. Second, we can easily add tracing.


import Control.Monad.Trans

-- The following is just the ordinary foldr, with a specialized
-- type for the seed: m z
foldrM :: Monad m =
  (a - m z - m z) - m z - [a] - m z
-- The code below is identical to that of foldr
foldrM f z [] = z
foldrM f z (h:t) = f h (foldrM f z t)

-- foldlM is identical Control.Monad.foldM 
-- Its code is shown below for reference.
foldlM, foldlM' :: Monad m =
  (z - a - m z) - z - [a] - m z
foldlM f z []= return z
foldlM f z (h:t) = f z h = \z' - foldlM f z' t

t1 = foldlM (\z a - putStrLn (foldlM:  ++ show a) 
 return (a:z)) [] [1,2,3]

{-
foldlM: 1
foldlM: 2
foldlM: 3
[3,2,1]
-}

-- foldlM' is foldlM expressed via foldrM
foldlM' f z l = 
foldrM (\e am - am = \k - return $ \z - f z e = k)
   (return return) l = \f - f z

-- foldrM'' is foldlM' with trace printing
foldlM'' :: (MonadIO m, Show a) =
  (z - a - m z) - z - [a] - m z
foldlM'' f z l = 
foldrM (\e am - liftIO (putStrLn $ foldR:  ++ show e) 
am = \k - return $ \z - f z e = k)
   (return return) l = \f - f z


t2 = foldlM'' (\z a - putStrLn (foldlM:  ++ show a) 
   return (a:z)) [] [1,2,3]

{-
foldR: 1
foldR: 2
foldR: 3
foldlM: 1
foldlM: 2
foldlM: 3
[3,2,1]
-}


As we can see from the trace printing, first the whole list is
traversed by foldR and the closure is constructed. Only after foldr
has finished, the closure is applied to z ([] in our case), and
foldl's function f gets a chance to work. The list is effectively
traversed twice, which means the `copy' of the list has to be
allocated -- that is, the closure that incorporates the calls to
f e1, f e2, etc. 


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


Re: [Haskell-cafe] ANN: data-fix-cse -- Common subexpression elimination for EDSLs

2013-02-19 Thread Anton Kholomiov
 Do you think the approach can be extended for non-regular (nested)
 algebraic types (where the recursive data type is sometimes at a different
 type instance)? For instance, it's very handy to use GADTs to capture
 embedded language types in host language (Haskell) types, which leads to
 non-regularity.


I'm not sure I understand the case you are talking about. Can you write a
simple example
of the types like this?

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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-19 Thread Jason Dagit
On Tue, Feb 19, 2013 at 3:01 PM, James Cook mo...@deepbondi.net wrote:

 On Feb 19, 2013, at 2:36 PM, Jan Stolarek jan.stola...@p.lodz.pl wrote:

  Anyway, how would you feel about changes that I would like to make:
  - move all modules into Lambdabot. namespace
  - remove unlambda, brainfuck and show from the repo. They are on
 hackage, no need to keep them
  here - these packages aren't even used in the build process.
  - cleanup scripts
  - add package versions to cabal file

 I have no objections to any of these, though I would recommend as Gwern
 hinted that if related packages are to be removed that they should also be
 given new homes - I believe that the lambdabot source is currently the main
 home of these packages.


Random thought, feel free to ignore it: Would it make sense to split
lambdabot up into core and contrib like is done with xmonad? Contrib could
contain the sillier things like bf, unlambda, show, etc and would have a
lower bar for contributors. Core would be the standard things and the
essential things.

It seems that people don't really contribute new plugins these days but it
would be great if they did. For example, having a plugin for liquid types
would be super spiffy. Also, any plugin that helps people to reason about
other code (like vacuum).

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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-19 Thread Jan Stolarek
Dnia wtorek, 19 lutego 2013, Gwern Branwen napisał:
 On Tue, Feb 19, 2013 at 5:36 PM, Jan Stolarek jan.stola...@p.lodz.pl wrote:
  - remove unlambda, brainfuck and show from the repo. They are on hackage,
  no need to keep them here - these packages aren't even used in the build
  process.

 Where will they go?
These packages are already on hackage:

http://hackage.haskell.org/package/brainfuck
http://hackage.haskell.org/package/show
http://hackage.haskell.org/package/unlambda

No need to keep them in the lambdabot repo.

Janek


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


[Haskell-cafe] Parser left recursion

2013-02-19 Thread Martin Drautzburg
Hello all,

this was previously asked on haskell-beginners, but only partially answered.

As an exercise I am writing a parser roughly following the expamples in Graham 
Hutton's book. The language contains things like:

data Exp = Lit Int -- literal integer
 | Plus Exp Exp

My naive parser enters an infinite recursion, when I try to parse 1+2. I do 
understand why:

hmm, this expression could be a plus, but then it must start with an 
expression, lets check. 

and it tries to parse expression again and again considers Plus.
  
Twan van Laarhoven told me that:

 Left-recursion is always a problem for recursive-descend parsers.

and suggested to do something like:

 parseExp = do
   lit - parseLit
   pluses - many (parsePlusToken * parseLit)
   return (combinePlusesWithLit lit pluses)

 combinePlusesWithLit = foldr Plus -- or foldl

This indeed does the trick, but only when the first token is a Lit (literal 
integer). 

I then added the possibility to optionally put things in parentheses. But then  
I cannot parse (1+2)+3. The original code fails, because (1+2) is not a 
Lit and when I allow an expression as the first argument to + I get infinite 
recursion again.

I am generally confused, that saying a plus expression is an integer followed 
by many plus somethings is not what the language says. So this requires a 
lot of paying attention to get right. I'd much rather say a plus expression 
is two expressions with a '+' in between.

I do know for sure, that it is possible to parse (1+2)+3 (ghci does it just 
fine). But I seem to be missing a trick.

Can anyone shed some light on this?

-- 
Martin

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


Re: [Haskell-cafe] Maintaining lambdabot

2013-02-19 Thread Jan Stolarek
 I have no objections to any of these, 
Great. Then I will start making mentioned changes and sending pull requests 
when I find some free 
time.

 though I would recommend as Gwern 
 hinted that if related packages are to be removed that they should also be
 given new homes - I believe that the lambdabot source is currently the main
 home of these packages.
OK, now I see. In that case we should create separate repositories for these 
packages.

 I tend to prefer not to give package version upper bounds
Seconded. I only want to specify lower bounds. I have already determined them 
so that code builds 
on GHC 7.4.2.

 Random thought, feel free to ignore it: Would it make sense to split 
 lambdabot up into core and 
contrib like is done with xmonad?
I don't have opinion on this one.

Janek


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


Re: [Haskell-cafe] Parser left recursion

2013-02-19 Thread Roman Cheplyaka
* Martin Drautzburg martin.drautzb...@web.de [2013-02-20 08:13:16+0100]
 I do know for sure, that it is possible to parse (1+2)+3 (ghci does it just 
 fine). But I seem to be missing a trick.
 
 Can anyone shed some light on this?

The trick in this case is that ghci doesn't use a recursive descent
parser — it uses an LR parser (generated by Happy).

Another workaround is to use memoization of some sort — see e.g. GLL
(Generalized LL) parsing.

Roman

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