Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-04 Thread Andrew Coppin

On 04/10/2011 07:08 AM, Dominique Devriese wrote:

All,

In case anyone is interested, I just want to point out an interesting
article about the relation between Haskell type classes and C++
(overloading + concepts):

http://sms.cs.chalmers.se/publications/papers/2008-WGP.pdf

Dominique


Thanks for that. A very interesting read...


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


Re: [Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread wren ng thornton

On 10/4/11 12:02 PM, Karel Gardas wrote:


Hello,

I'm trying to find out if it's possible to use Haskell data type
definition capability to define types and compile defined types into
other languages, for example into Google's protocol buffers data
definition language. So basically speaking I'm thinking about using
Haskell sub-set as a data-definition DSL together with some functions
which will generate some code based on supplied defined data types. My
idea is:


If your main goal is to use protocol buffers in Haskell, then I'd 
recommend checking out Chris Kuklewicz's packages: hprotoc, 
protocol-buffers, protocol-buffers-descriptor.


If your main goal is actually to have a DSL, well, the other folk's 
comments about generic programing techniques should help.


--
Live well,
~wren

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


[Haskell-cafe] ANN: hledger-web 0.16.3

2011-10-04 Thread Simon Michael
I believe this release of hledger-web is really and truly installable from 
hackage. Thanks for the problem reports! Details at 
http://hledger.org/NEWS.html .


On Oct 1, 2011, at 10:22 AM, Simon Michael wrote:

> I'm pleased to announce version 0.16 of the hledger packages. This is a
> stability/bugfix/polish release (which may become the pattern for
> even-numbered releases in future.)
> 
> hledger is a library and set of user tools for working with financial
> data (or anything that can be tracked in a double-entry accounting
> ledger.) It is a haskell port and friendly fork of John Wiegley's
> Ledger. hledger provides command-line, curses and web interfaces, and
> aims to be a reliable, practical tool for daily use.  Given a plain
> text file describing transactions of money or any other commodity, it
> will print the chart of accounts, account balances, or just the
> transactions you're interested in.  It can also help you record new
> transactions, or convert CSV data from your bank.
> 
> Home: http://hledger.org
> 
> To install: cabal update, cabal install hledger. If you have trouble, let
> me know or watch the mail list/bug tracker for updates. Optional add-ons:
> hledger-web hledger-vty hledger-chart hledger-interest.


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


Re: [Haskell-cafe] ANN: hit a reimplementation of git storage in haskell.

2011-10-04 Thread Conrad Parker
Hi Vincent,

great stuff!

I've also got an in-progress toy git clone called ght:
http://github.com/kfish/ght. It only reads, no write support and no
revspec parsing. I tried to keep close to the git design, using mmap
and Ptr-based binary search to read pack indices etc. Doing so seems
fairly un-Haskelly but turned out surprisingly neat, what with Haskell
being the world's finest imperative programming language and all.

Conrad.

On 5 October 2011 05:15, Vincent Hanquez  wrote:
> Hi Haskellers,
>
> I just want to announce the hit project [1], which is a reimplementation of
> low level git operations to read *AND* write to a git repository. It support
> reading from anything i threw at it (loose objects, packed objects, deltas),
> a subset of revisions specifier (man gitrevisions), and writing new objects
> (blob, tree, commit, tag).
>
> I don't necessarily want to re-implement git itself (although patches
> welcome if someone want to go in this direction), and as such the project is
> a bit of a toy to investigate git storage (for another project of mine) and
> superseeding my own libgit project (for yet another project). Yet it should
> be completely functional and have good performance.
>
> A few word of the implementation: it's very IO based at the moment; The way
> things are done by git, doesn't necessarily cope with pure and nice stuff if
> performance need to follow. That said it should still be easier to
> understand than reading the git source :-)
>
> Any comments welcome,
>
> [1] http://hackage.haskell.org/package/hit/
>
> --
> Vincent
>
> ___
> 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] Fwd: LZMA for Haskell?

2011-10-04 Thread Nathan Howell
lzma.h is part of the xz-utils package, which is available here:
http://tukaani.org/xz/

If you have any problems with the package let me know.

On Tue, Oct 4, 2011 at 3:34 PM, Paulo Pocinho  wrote:

> (Thought it would be better to put this in the haskell-cafe list).
>
> Hello list.
>
> I'd like to use LZMA to create/extract archives and compare CRC from
> archived files. What do I need to use LZMA in Haskell?
>
> There is a page called "Library/Compression" in the wiki [1] but it is
> from 2005, using LZMA version 4.06. Besides being old, I can only find
> the LZMA SDK version 9.20 for download.
>
> The only related package I can find on hackage is lzma-enumerator [2].
> Trying to install with cabal requires an old header named lzma.h that
> is no longer available.
>
> [1] http://www.haskell.org/haskellwiki/Library/Compression
> [2] http://hackage.haskell.org/package/lzma-enumerator
>
> ___
> 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


[Haskell-cafe] Fwd: LZMA for Haskell?

2011-10-04 Thread Paulo Pocinho
(Thought it would be better to put this in the haskell-cafe list).

Hello list.

I'd like to use LZMA to create/extract archives and compare CRC from
archived files. What do I need to use LZMA in Haskell?

There is a page called "Library/Compression" in the wiki [1] but it is
from 2005, using LZMA version 4.06. Besides being old, I can only find
the LZMA SDK version 9.20 for download.

The only related package I can find on hackage is lzma-enumerator [2].
Trying to install with cabal requires an old header named lzma.h that
is no longer available.

[1] http://www.haskell.org/haskellwiki/Library/Compression
[2] http://hackage.haskell.org/package/lzma-enumerator

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


Re: [Haskell-cafe] ANN: hit a reimplementation of git storage in haskell.

2011-10-04 Thread Jason Dagit
On Tue, Oct 4, 2011 at 2:15 PM, Vincent Hanquez  wrote:

> Any comments welcome,

Nice!  Have you looked at Petr Rockai's hashed-storage?
http://hackage.haskell.org/package/hashed-storage-0.5.8

Jason

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


Re: [Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Erik Hesselink
On Tue, Oct 4, 2011 at 20:33, Karel Gardas  wrote:
> data PersonType = Person {
>        id :: Int
>        , name :: String
>        , email :: Maybe String
>        }
>        deriving (Show, Data, Typeable)
>
>
> so I have `PersonType' as type constructor and Person as value constructor
> (or data constructor) -- speaking using terms from Real World Haskell,
> Chapter 3[1]. And now I see that none of typeOf/dataTypeOf/toContr is
> applicable to *type constructor* but all are applicable to *value/data
> constructor*. Ditto happen when testing Color versus RED, GREEN, BLUE. At
> least GHCi complains this way:
>
> *Main> typeOf Color
>
> :0:8: Not in scope: data constructor `Color'
> *Main> typeOf PersonType
>
> :0:8: Not in scope: data constructor `PersonType'
>
> But, I'd like to start processing of data definition from the *type
> constructor*. So:
>
> emit_proto PersonType 1
> emit_proto Color 1
>
> Is that possible at all? I mean in the scope/context of GHC's
> Data/Data.Data/Data.Typeable etc. modules. (w/o considering TH now).

A definition of 'typeOf' is not supposed to use its argument, since
the normal way to call it is to pass undefined. The documentation
says:

"The value of the argument should be ignored by any instance of
Typeable, so that it is safe to pass undefined as the argument. "

So you should call it like:

typeOf (undefined :: PersonType).

Erik

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


[Haskell-cafe] ANN: hit a reimplementation of git storage in haskell.

2011-10-04 Thread Vincent Hanquez

Hi Haskellers,

I just want to announce the hit project [1], which is a reimplementation of low 
level git operations to read *AND* write to a git repository. It support reading 
from anything i threw at it (loose objects, packed objects, deltas), a subset of 
revisions specifier (man gitrevisions), and writing new objects (blob, tree, 
commit, tag).


I don't necessarily want to re-implement git itself (although patches welcome if 
someone want to go in this direction), and as such the project is a bit of a toy 
to investigate git storage (for another project of mine) and superseeding my own 
libgit project (for yet another project). Yet it should be completely functional 
and have good performance.


A few word of the implementation: it's very IO based at the moment; The way 
things are done by git, doesn't necessarily cope with pure and nice stuff if 
performance need to follow. That said it should still be easier to understand 
than reading the git source :-)


Any comments welcome,

[1] http://hackage.haskell.org/package/hit/

--
Vincent

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


Re: [Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Antoine Latter
On Tue, Oct 4, 2011 at 1:33 PM, Karel Gardas  wrote:
>
> Hello,
>
> thanks a lot to Edward, Jose, Ryan and Stephen for fast reply in this
> thread. I see I've not been that precise in specification of what I need
> exactly so I need to add this: I've changed a little bit definition of
> person to:
>
> data PersonType = Person {
>        id :: Int
>        , name :: String
>        , email :: Maybe String
>        }
>        deriving (Show, Data, Typeable)
>
>
> so I have `PersonType' as type constructor and Person as value constructor
> (or data constructor) -- speaking using terms from Real World Haskell,
> Chapter 3[1]. And now I see that none of typeOf/dataTypeOf/toContr is
> applicable to *type constructor* but all are applicable to *value/data
> constructor*. Ditto happen when testing Color versus RED, GREEN, BLUE. At
> least GHCi complains this way:
>
> *Main> typeOf Color
>
> :0:8: Not in scope: data constructor `Color'
> *Main> typeOf PersonType
>
> :0:8: Not in scope: data constructor `PersonType'
>
> But, I'd like to start processing of data definition from the *type
> constructor*. So:
>
> emit_proto PersonType 1
> emit_proto Color 1
>

You could use Data.Proxy and pass a type proxy as the first argument:

> emit_proto (Proxy :: Proxy MyType) 1

It seems like you could then do something like `dataTypeOf
(asProxyTypeOf undefined proxy)` to unpack the 'Data' instance of the
proxied type. There might be a better way, but this is just what I can
think of off the top of my head.

The 'Poxy' type is here:

http://hackage.haskell.org/packages/archive/tagged/0.2.3.1/doc/html/Data-Proxy.html

Antoine

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


Re: [Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Karel Gardas


Forgotten note: GHC's Generics as described here: 
http://haskell.org/ghc/docs/latest/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html#t:Datatype 
-- is not yet clear to me, I'm searching for more information about this 
in the meantime...


Karel

On 10/ 4/11 08:33 PM, Karel Gardas wrote:


Hello,

thanks a lot to Edward, Jose, Ryan and Stephen for fast reply in this
thread. I see I've not been that precise in specification of what I need
exactly so I need to add this: I've changed a little bit definition of
person to:

data PersonType = Person {
id :: Int
, name :: String
, email :: Maybe String
}
deriving (Show, Data, Typeable)


so I have `PersonType' as type constructor and Person as value
constructor (or data constructor) -- speaking using terms from Real
World Haskell, Chapter 3[1]. And now I see that none of
typeOf/dataTypeOf/toContr is applicable to *type constructor* but all
are applicable to *value/data constructor*. Ditto happen when testing
Color versus RED, GREEN, BLUE. At least GHCi complains this way:

*Main> typeOf Color

:0:8: Not in scope: data constructor `Color'
*Main> typeOf PersonType

:0:8: Not in scope: data constructor `PersonType'

But, I'd like to start processing of data definition from the *type
constructor*. So:

emit_proto PersonType 1
emit_proto Color 1

Is that possible at all? I mean in the scope/context of GHC's
Data/Data.Data/Data.Typeable etc. modules. (w/o considering TH now).

Thanks!
Karel


[1]:
http://book.realworldhaskell.org/read/defining-types-streamlining-functions.html




On 10/ 4/11 06:02 PM, Karel Gardas wrote:


Hello,

I'm trying to find out if it's possible to use Haskell data type
definition capability to define types and compile defined types into
other languages, for example into Google's protocol buffers data
definition language. So basically speaking I'm thinking about using
Haskell sub-set as a data-definition DSL together with some functions
which will generate some code based on supplied defined data types. My
idea is:

data Person = Person {
id :: Int
, name :: String
, email :: Maybe String
}
deriving (Show, Data, Typeable)

emit_proto Person 1

where emit_proto is function which will translate Person data type
definition into Google's proto language (the 1 is index from which start
to index type's fields) by traversing data type definition and
translating all its children plus do some header/footer generation etc:

message Person {
required int32 id = 1;
required string name = 2;
optional string email = 3;
}

I've looked for something like that and found SYB papers which works on
top of data instance (i.e. actual data, not data type). I also found
JSON lib which again works on top of data and not data type. I've tried
to look into Data.Typetable etc, but have not found function which will
print data type's field name and field type name (although JSON lib
seems to use field name for JSON generation so I'll need to investigate
this more). I've tested `typeOf' function and it's quite useful, but its
limitation is that it's not working on ADT name:

data Color = RED|GREEN|BLUE

*Main> typeOf Color

:1:8: Not in scope: data constructor `Color'

*Main> typeOf RED
Main.Color

and I would need that in order to translate Color defined above into
enum like:

enum Color {
RED = 0;
GREEN = 1;
BLUE = 2;
}


My question is: do you think I'm looking into good direction (i.e.
Data/Typeable) or do you think I'll need to use something different for
data definition DSL (Template Haskell?, or impossible in Haskell so
write my own language with full parser? etc?)

Thanks for any idea or opinion on this!
Karel

___
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] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Karel Gardas


Hello,

thanks a lot to Edward, Jose, Ryan and Stephen for fast reply in this 
thread. I see I've not been that precise in specification of what I need 
exactly so I need to add this: I've changed a little bit definition of 
person to:


data PersonType = Person {
id :: Int
, name :: String
, email :: Maybe String
}
deriving (Show, Data, Typeable)


so I have `PersonType' as type constructor and Person as value 
constructor (or data constructor) -- speaking using terms from Real 
World Haskell, Chapter 3[1]. And now I see that none of 
typeOf/dataTypeOf/toContr is applicable to *type constructor* but all 
are applicable to *value/data constructor*. Ditto happen when testing 
Color versus RED, GREEN, BLUE. At least GHCi complains this way:


*Main> typeOf Color

:0:8: Not in scope: data constructor `Color'
*Main> typeOf PersonType

:0:8: Not in scope: data constructor `PersonType'

But, I'd like to start processing of data definition from the *type 
constructor*. So:


emit_proto PersonType 1
emit_proto Color 1

Is that possible at all? I mean in the scope/context of GHC's 
Data/Data.Data/Data.Typeable etc. modules. (w/o considering TH now).


Thanks!
Karel


[1]: 
http://book.realworldhaskell.org/read/defining-types-streamlining-functions.html




On 10/ 4/11 06:02 PM, Karel Gardas wrote:


Hello,

I'm trying to find out if it's possible to use Haskell data type
definition capability to define types and compile defined types into
other languages, for example into Google's protocol buffers data
definition language. So basically speaking I'm thinking about using
Haskell sub-set as a data-definition DSL together with some functions
which will generate some code based on supplied defined data types. My
idea is:

data Person = Person {
id :: Int
, name :: String
, email :: Maybe String
}
deriving (Show, Data, Typeable)

emit_proto Person 1

where emit_proto is function which will translate Person data type
definition into Google's proto language (the 1 is index from which start
to index type's fields) by traversing data type definition and
translating all its children plus do some header/footer generation etc:

message Person {
required int32 id = 1;
required string name = 2;
optional string email = 3;
}

I've looked for something like that and found SYB papers which works on
top of data instance (i.e. actual data, not data type). I also found
JSON lib which again works on top of data and not data type. I've tried
to look into Data.Typetable etc, but have not found function which will
print data type's field name and field type name (although JSON lib
seems to use field name for JSON generation so I'll need to investigate
this more). I've tested `typeOf' function and it's quite useful, but its
limitation is that it's not working on ADT name:

data Color = RED|GREEN|BLUE

*Main> typeOf Color

:1:8: Not in scope: data constructor `Color'

*Main> typeOf RED
Main.Color

and I would need that in order to translate Color defined above into
enum like:

enum Color {
RED = 0;
GREEN = 1;
BLUE = 2;
}


My question is: do you think I'm looking into good direction (i.e.
Data/Typeable) or do you think I'll need to use something different for
data definition DSL (Template Haskell?, or impossible in Haskell so
write my own language with full parser? etc?)

Thanks for any idea or opinion on this!
Karel

___
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] ANN: OpenCL 1.0.1.3 package

2011-10-04 Thread Jason Dagit
On Tue, Oct 4, 2011 at 12:54 AM, Luis Cabellos  wrote:

> I understand your point. I didn't know the problems with cross module
> inlining that Haskell suffers. I learned the BSD3, I think is a good  and
> I'll change it on github and I'll put in the next release.

Oh cool.  Thanks!  I think that's for the best.  Someone sent me a
link to this offline:
https://github.com/judah/HsOpenCL

Maybe the two implementations can be merged into one super implementation :)

>> http://www.khronos.org/registry/cl/sdk/1.0/docs/man/xhtml/clGetDeviceInfo.html
>
> I use the pattern get[Type]Info -> to get[Type][specificInfo] where
> specificInfo is the OpenCL name of an enumerate. I don't know if your
> proposal, I open a ticket on github to think about.

I see.  My experience with the OpenGL bindings is that it can still be
confusing for users of the library.  The reason is simple, there are
good docs for using the API from C and those docs tend to match the
official specification.  So people who are new to the Haskell bindings
will need some documentation that explains how to go from the C API to
the Haskell API.  Otherwise users will need to read the source code
directly to figure out where the function they need to call is
located.  Good haddocks help, but that's just one part of the
solution.  Being able to search for the function by name is also
useful, so that's why I proposed adding something on to the end of the
function name.  So that people using search in their browser on the
haddocks or using grep at the command line would find the function(s)
they are looking for and (hopefully) minimize time spent searching.

It's a shame because, if we had dependent types we could encode the C
API directly into Haskell.

Thanks and I'll probably look at it some more this weekend.  I have a
test program I'm working on but I would need to port it to your
bindings.

Also, if you use the #fun macro from c2hs to create the foreign
imports you will need to use at least version 0.16.4 as previous
versions do not honor stdcall.

Jason

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


Re: [Haskell-cafe] Composing a list of Enumeratees into an Enumerator using ($=)

2011-10-04 Thread Román González
Hello guys,

After some playing around trying to compose enumerators, I went through a
different approach and tried instead to compose through Iteratees.

The following code does compile correctly

import Data.List (foldl')
import Data.Enumerator hiding (foldl')
import qualified Data.Enumerator.List as EL

-- This is what I orginally have
--main :: IO ()
--main = run_ (((enumList 5 [1..] $=
--   EL.isolate 100) $=
--   EL.filter ((== 0) . (`mod` 2))) $$
--   EL.consume) >>=
--   print

-- This is what I want and for some reason is not
-- compiling (infinite type error)
--main2 :: IO ()
--main2 = run (enum $$ EL.consume) >>= print
-- where
--   enum = foldl' ($=)
-- (enumList 5 [1..])
-- [ EL.isolate 100
-- , EL.filter ((==0) . (`mod` 2))
-- ]

main :: IO ()
main = run (enum $$ it) >>= print
 where
   enum = enumList 5 [1..]
   it   = foldr (=$)
EL.consume
[ EL.isolate 100
, EL.filter ((==0) . (`mod` 2))
]


It seems the (=$) operator behaves in a better way than the ($=) operator...
When I check the signatures of both functions

> :t ($=)
($=)
  :: Monad m =>
 Enumerator ao m (Step ai m b)
 -> Enumeratee ao ai m b
 -> Enumerator ai m b

The original enumerator of type (Enumerator a m b) gets transformed to
(Enumerator ao m (Step ai m b)), how this works is beyond me.

When checking the type of (=$)
> :t ($=)
(=$)
  :: Monad m =>
 Enumeratee ao ai m b -> Iteratee ai m b -> Iteratee ao m b

Returns something with more sense, when using an Iteratee as a base of a
foldr of enumeratees, the response for the next one will always be an Iteratee
ao m b, the return type of the Iteratee is not changed with a Step type
suddenly like in ($=).

I solved my problem, however I'm really curious to know what is going on
with the types when using the ($=) operator, I'm going to investigate on my
part and try to come with some clear explanation, however if anyone can
chime in and give us some insights, they are more than welcome.

Cheers.

Roman.-

2011/10/4 Román González 

> Hello Conrad,
>
>
> Thanks for taking the time to answer back. Actually I don't want to do
> anything fancy, I just want to compose a list of Enumeratees together into
> an Enumerator, using the same type for both ao and ai, I suspect it
> doesn't matter what the type of this ao and ai are, I would obtain the same
> error using this simpler example:
>
> module Main where
>
> import Data.List (foldl')
> import Data.Enumerator hiding (foldl')
> import qualified Data.Enumerator.List as EL
>
> -- This is what I orginally have
> main :: IO ()
> main = run_ (((enumList 5 [1..] $=
>EL.isolate 100) $=
>EL.filter ((== 0) . (`mod` 2))) $$
>EL.consume) >>=
>print
>
> -- This is what I want and for some reason is not
> -- compiling (infinite type error)
> --main2 :: IO ()
> --main2 = run (enum $$ EL.consume) >>= print
> -- where
> --   enum = foldl' ($=)
> -- (enumList 5 [1..])
> -- [ EL.isolate 100
> -- , EL.filter ((==0) . (`mod` 2))
> -- ]
>
>
>
> For some complicated type logic, main2 won't compile, I'm trying to figure
> out a way to actually do this. The reason why I want to do the composition
> through list is because I'm mapping input parameters (from
> System.Environment.getArgs) to a list of Enumeratees, and I want to compose
> them dynamically.
>
> Hope this helps.
>
> Roman.-
>
> 2011/10/3 Conrad Parker 
>
>> 2011/10/4 Román González :
>> > Hey guys,
>> >
>> > Right now I'm facing with a type problem that is really nasty, I want to
>> > compose a list of enumeratees using the ($=) operator to create a new
>> > enumerator.  Whenever I'm trying to use the foldx function in
>> conjunction
>> > with ($=) I get this error:
>> >
>> >> :t foldr ($=)
>> >
>> > :1:7:
>> > Occurs check: cannot construct the infinite type:
>> >   b0 = Step ao0 m0 b0
>> > Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
>> >-> Enumeratee ao0 ao0 m0 b0
>> >-> Enumeratee ao0 ao0 m0 b0
>> >   Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
>> >-> Enumeratee ao0 ao0 m0 b0
>> >-> Enumerator ao0 m0 b0
>> > In the first argument of `foldr', namely `($=)'
>> > In the expression: foldr ($=)
>> >
>> >> :t Prelude.foldl ($=)
>> >
>> > :1:15:
>> > Occurs check: cannot construct the infinite type:
>> >   b0 = Step ao0 m0 b0
>> > Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
>> >-> Enumeratee ao0 ao0 m0 b0
>> >-> Enumerator ao0 m0 (Step ao0 m0 b0)
>> >   Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
>> >-> Enumeratee ao0 ao0 m0 b0
>> >-> Enumerator ao0 m0 b0
>> > In the first argument of `

Re: [Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Stephen Tetley
On 4 October 2011 17:02, Karel Gardas  wrote:
>
> Hello,

[SNIP]

> So
> basically speaking I'm thinking about using Haskell sub-set as a
> data-definition DSL together with some functions which will generate some
> code based on supplied defined data types. ...

This seems reminiscent of ASDL - the Abstract Syntax Definition
Language - and ASDLgen (its generator) which used sum and product
types (essentially the same a Haskell or ML's algebraic types) to
define data for compiler internals. The definitions could be compiled
to C++, C, Java, ML, and Haskell. As well as data type definitions
ASDLgen generated marshallers for the ASDL binary format.

Unfortunately the Zephyr project which sponsored ASDL seems to have
had an early demise - so what info there still is available on the web
might be patchy.

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


Re: [Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Ryan Newton
An interesting and semi-related project was just presented at ICFP by
Kathleen Fisher.  It's called "Forest" and uses template haskell to create
schema's for "FileStores" from Haskell definitions.  But they're not
plain-old-haskell type definitions...

  -Ryan


On Tue, Oct 4, 2011 at 12:11 PM, Edward Z. Yang  wrote:

> Just making sure: have you looked at the Data.Data module yet?
>
> Edward
>
> Excerpts from Karel Gardas's message of Tue Oct 04 12:02:34 -0400 2011:
> >
> > Hello,
> >
> > I'm trying to find out if it's possible to use Haskell data type
> > definition capability to define types and compile defined types into
> > other languages, for example into Google's protocol buffers data
> > definition language. So basically speaking I'm thinking about using
> > Haskell sub-set as a data-definition DSL together with some functions
> > which will generate some code based on supplied defined data types. My
> > idea is:
> >
> > data Person = Person {
> >  id :: Int
> >  , name :: String
> >  , email :: Maybe String
> >  }
> >  deriving (Show, Data, Typeable)
> >
> > emit_proto Person 1
> >
> > where emit_proto is function which will translate Person data type
> > definition into Google's proto language (the 1 is index from which start
> > to index type's fields) by traversing data type definition and
> > translating all its children plus do some header/footer generation etc:
> >
> > message Person {
> >required int32 id = 1;
> >required string name = 2;
> >optional string email = 3;
> > }
> >
> > I've looked for something like that and found SYB papers which works on
> > top of data instance (i.e. actual data, not data type). I also found
> > JSON lib which again works on top of data and not data type. I've tried
> > to look into Data.Typetable etc, but have not found function which will
> > print data type's field name and field type name (although JSON lib
> > seems to use field name for JSON generation so I'll need to investigate
> > this more). I've tested `typeOf' function and it's quite useful, but its
> > limitation is that it's not working on ADT name:
> >
> > data Color = RED|GREEN|BLUE
> >
> > *Main> typeOf Color
> >
> > :1:8: Not in scope: data constructor `Color'
> >
> > *Main> typeOf RED
> > Main.Color
> >
> > and I would need that in order to translate Color defined above into
> > enum like:
> >
> > enum Color {
> >RED = 0;
> >GREEN = 1;
> >BLUE = 2;
> > }
> >
> >
> > My question is: do you think I'm looking into good direction (i.e.
> > Data/Typeable) or do you think I'll need to use something different for
> > data definition DSL (Template Haskell?, or impossible in Haskell so
> > write my own language with full parser? etc?)
> >
> > Thanks for any idea or opinion on this!
> > Karel
> >
>
> ___
> 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] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread José Pedro Magalhães
Hi Karel,

You can use SYB's toConstr/dataTypeOf [1] to obtain information about the
name of the constructor and datatype. Alternatively, you can also use the
new generic programming framework of ghc-7.2 [2].


Cheers,
Pedro

[1]
http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Data.html#v:toConstr
[2]
http://haskell.org/ghc/docs/latest/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html#t:Datatype

On Tue, Oct 4, 2011 at 17:02, Karel Gardas  wrote:

>
> Hello,
>
> I'm trying to find out if it's possible to use Haskell data type definition
> capability to define types and compile defined types into other languages,
> for example into Google's protocol buffers data definition language. So
> basically speaking I'm thinking about using Haskell sub-set as a
> data-definition DSL together with some functions which will generate some
> code based on supplied defined data types. My idea is:
>
> data Person = Person {
>id :: Int
>, name :: String
>, email :: Maybe String
>}
>deriving (Show, Data, Typeable)
>
> emit_proto Person 1
>
> where emit_proto is function which will translate Person data type
> definition into Google's proto language (the 1 is index from which start to
> index type's fields) by traversing data type definition and translating all
> its children plus do some header/footer generation etc:
>
> message Person {
>  required int32 id = 1;
>  required string name = 2;
>  optional string email = 3;
> }
>
> I've looked for something like that and found SYB papers which works on top
> of data instance (i.e. actual data, not data type). I also found JSON lib
> which again works on top of data and not data type. I've tried to look into
> Data.Typetable etc, but have not found function which will print data type's
> field name and field type name (although JSON lib seems to use field name
> for JSON generation so I'll need to investigate this more). I've tested
> `typeOf' function and it's quite useful, but its limitation is that it's not
> working on ADT name:
>
> data Color = RED|GREEN|BLUE
>
> *Main> typeOf Color
>
> :1:8: Not in scope: data constructor `Color'
>
> *Main> typeOf RED
> Main.Color
>
> and I would need that in order to translate Color defined above into enum
> like:
>
> enum Color {
>  RED = 0;
>  GREEN = 1;
>  BLUE = 2;
> }
>
>
> My question is: do you think I'm looking into good direction (i.e.
> Data/Typeable) or do you think I'll need to use something different for data
> definition DSL (Template Haskell?, or impossible in Haskell so write my own
> language with full parser? etc?)
>
> Thanks for any idea or opinion on this!
> Karel
>
> __**_
> 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] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Edward Z. Yang
Just making sure: have you looked at the Data.Data module yet?

Edward

Excerpts from Karel Gardas's message of Tue Oct 04 12:02:34 -0400 2011:
> 
> Hello,
> 
> I'm trying to find out if it's possible to use Haskell data type 
> definition capability to define types and compile defined types into 
> other languages, for example into Google's protocol buffers data 
> definition language. So basically speaking I'm thinking about using 
> Haskell sub-set as a data-definition DSL together with some functions 
> which will generate some code based on supplied defined data types. My 
> idea is:
> 
> data Person = Person {
>  id :: Int
>  , name :: String
>  , email :: Maybe String
>  }
>  deriving (Show, Data, Typeable)
> 
> emit_proto Person 1
> 
> where emit_proto is function which will translate Person data type 
> definition into Google's proto language (the 1 is index from which start 
> to index type's fields) by traversing data type definition and 
> translating all its children plus do some header/footer generation etc:
> 
> message Person {
>required int32 id = 1;
>required string name = 2;
>optional string email = 3;
> }
> 
> I've looked for something like that and found SYB papers which works on 
> top of data instance (i.e. actual data, not data type). I also found 
> JSON lib which again works on top of data and not data type. I've tried 
> to look into Data.Typetable etc, but have not found function which will 
> print data type's field name and field type name (although JSON lib 
> seems to use field name for JSON generation so I'll need to investigate 
> this more). I've tested `typeOf' function and it's quite useful, but its 
> limitation is that it's not working on ADT name:
> 
> data Color = RED|GREEN|BLUE
> 
> *Main> typeOf Color
> 
> :1:8: Not in scope: data constructor `Color'
> 
> *Main> typeOf RED
> Main.Color
> 
> and I would need that in order to translate Color defined above into 
> enum like:
> 
> enum Color {
>RED = 0;
>GREEN = 1;
>BLUE = 2;
> }
> 
> 
> My question is: do you think I'm looking into good direction (i.e. 
> Data/Typeable) or do you think I'll need to use something different for 
> data definition DSL (Template Haskell?, or impossible in Haskell so 
> write my own language with full parser? etc?)
> 
> Thanks for any idea or opinion on this!
> Karel
> 

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


[Haskell-cafe] DSL for data definition (e.g. compiling Haskell type defs into Google's protocol buffers type defs)

2011-10-04 Thread Karel Gardas


Hello,

I'm trying to find out if it's possible to use Haskell data type 
definition capability to define types and compile defined types into 
other languages, for example into Google's protocol buffers data 
definition language. So basically speaking I'm thinking about using 
Haskell sub-set as a data-definition DSL together with some functions 
which will generate some code based on supplied defined data types. My 
idea is:


data Person = Person {
id :: Int
, name :: String
, email :: Maybe String
}
deriving (Show, Data, Typeable)

emit_proto Person 1

where emit_proto is function which will translate Person data type 
definition into Google's proto language (the 1 is index from which start 
to index type's fields) by traversing data type definition and 
translating all its children plus do some header/footer generation etc:


message Person {
  required int32 id = 1;
  required string name = 2;
  optional string email = 3;
}

I've looked for something like that and found SYB papers which works on 
top of data instance (i.e. actual data, not data type). I also found 
JSON lib which again works on top of data and not data type. I've tried 
to look into Data.Typetable etc, but have not found function which will 
print data type's field name and field type name (although JSON lib 
seems to use field name for JSON generation so I'll need to investigate 
this more). I've tested `typeOf' function and it's quite useful, but its 
limitation is that it's not working on ADT name:


data Color = RED|GREEN|BLUE

*Main> typeOf Color

:1:8: Not in scope: data constructor `Color'

*Main> typeOf RED
Main.Color

and I would need that in order to translate Color defined above into 
enum like:


enum Color {
  RED = 0;
  GREEN = 1;
  BLUE = 2;
}


My question is: do you think I'm looking into good direction (i.e. 
Data/Typeable) or do you think I'll need to use something different for 
data definition DSL (Template Haskell?, or impossible in Haskell so 
write my own language with full parser? etc?)


Thanks for any idea or opinion on this!
Karel

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


Re: [Haskell-cafe] ANN: OpenCL 1.0.1.3 package

2011-10-04 Thread Ketil Malde
Luis Cabellos  writes:

>  * The main reason is that I'm not comfortable with the license
> you're using.  The original code by Jeff Heard was BSD3 with an
> additional copyright notice.  Your code is AGPL3.  The GPL is known to
> cause problems with Haskell code due to cross module inlining.  I
> don't know how the "A" in AGPL changes things.

I don't think inlining matters in this case.  If you distribute a work
incorporating GPL code, you must allow the recipient to redistribute it
(including all sources) under the GPL.  Clearly, GPL code is not
suitable when you wish to redistribute it along with proprietary code,
but it should be unproblematic for most open source projects.

For *L*GPL code, the intention is that it can apply to a library,
distributed as a separate unit, and allowing it to be *used* as such,
also by proprietary applications.  Inlining through static linking may
affect this, as it incorporates actual code from the LGPL
library in a program that is then distributed as a propietary, binary
object.

> I understand your point. I didn't know the problems with cross module
> inlining that Haskell suffers. I learned the BSD3, I think is a good  and
> I'll change it on github and I'll put in the next release.

If you are happy with BSD3, that license is the one which will make your
code most generally useful.  The intent behind the GPL family is to make the
code useful to those who reciprocate the sentiment, and less useful to
those who don't.  In practice, it is rare that BSD3 licensed libraries
are made proprietary, it is often to everybody's benefit that thinks are
maintained in the open.  The general sentiment in the Haskell community
is a preference for BSD.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Is it possible to represent such polymorphism?

2011-10-04 Thread oleg

sdiyazg at sjtu.edu.cn wrote:

> >> generalizedFilterMap (\[x,y,z]-> if(x==1&&z==1)then [y*10] else  
> >> [0]) (3,1) [1,2,3,4,1,2,1,3,1,4,1,5,2]
> [0,0,0,0,20,0,30,0,40,0,0]
>
> Of course, I could have simply used [Int] , (Num a)=>[a] or
> (Int,Int,Int), but I'm trying to write code as generic as possible.

As I understand, the point of generalizedFilterMap is to permit the
filter function to examine several elements of the list within the
current window (rather than just the current element). The step argument
determines the step of sliding the window. Further, you wish to make
the step argument default (setting it to 1 if not given).

First of all, if you are interested in stencil computations, there are
several good packages and even the whole DSLs:

  http://research.microsoft.com/en-us/um/people/simonpj/papers/ndp/index.htm
  http://arxiv.org/abs/1109.0777
  http://people.csail.mit.edu/yuantang/

Second, the given code is not as generic as possible. In the above
example, the filter function examines values within the window of size
3. That fact has to be specified twice: in the pattern \ [x,y,z] -> ...
and as the number 3. Having to specify the same information twice is
always less than satisfactory: if we expand the pattern to
\ [x,y,z,u] -> we have to remember to update the other argument to the
function.

There are many solutions to the problem, involving as much type
hacking as one may wish (some of the stencil packages above do track
the size of the stencil statically, in types). Perhaps one of the simplest
solution is the following


> generalizedFilterMap3 :: Int -> ([a]->[a]) -> [a] -> [a]
> generalizedFilterMap3 step f = concatMap f . decimate step . tails
>
> -- pick every n-th
> decimate :: Int -> [a] -> [a]
> decimate 1 lst = lst
> decimate _ [] = []
> decimate n lst = head lst : decimate n (drop n lst)
>
> test1 = generalizedFilterMap3 1 f [1,2,3,4,1,2,1,3,1,4,1,5,2]
>  where
>  f (x:y:z:_) = if x==1&&z==1 then [y*10] else [0]
>  f _ = []

Again there are many, many approaches to default arguments. Perhaps
the simplest, involving no typeclasses and no type computation is the
following

> data GMapArgs a = GMapDflt{step  :: Int,
>gmapf :: [a] -> [a]}
>
> dflt = GMapDflt{step = 1, gmapf = id}
>
> generalizedFilterMap dflt = generalizedFilterMap3 (step dflt) (gmapf dflt)
>
> test2 = generalizedFilterMap dflt{gmapf=f} [1,2,3,4,1,2,1,3,1,4,1,5,2]
>  where
>  f (x:y:z:_) = if x==1&&z==1 then [y*10] else [0]
>  f _ = []
>
> test3 = generalizedFilterMap dflt{gmapf=f,step=2} [1,2,3,4,1,2,1,3,1,4,1,5,2]
>  where
>  f (x:y:z:_) = if x==1&&z==1 then [y*10] else [0]
>  f _ = []

It requires no extensions. Record puns and other Record extensions
make the approach nicer.


> What I want is some thing like this in C++:
>
> float f(char x){ return 0.1f; }
> int f(double x){ return 1; }

One should point out the difficulties of comparing C++ with
Haskell. Haskell is designed to be higher-order, making it simple to
pass functions as arguments to other functions. Your code for generic
maps relies on that behavior. Try passing the overloaded C++ function
'f' defined above to some other function. That is, implement something
like the following
float g(??? f) { return f('x') + f(1.0); }
int main(void) {printf("%g",g(f)); return 0;}

One can certainly implement the above outline in C++, but it won't be
simple.


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


Re: [Haskell-cafe] ANN: OpenCL 1.0.1.3 package

2011-10-04 Thread Luis Cabellos
On Mon, Oct 3, 2011 at 6:04 PM, Jason Dagit  wrote:

> On Mon, Oct 3, 2011 at 3:56 AM, Luis Cabellos 
> wrote:Your bindings are a higher quality than the the OpenCLRaw bindings and
> you're doing good technical work, but I stopped using your bindings
> for a couple reasons:
>  * The main reason is that I'm not comfortable with the license
> you're using.  The original code by Jeff Heard was BSD3 with an
> additional copyright notice.  Your code is AGPL3.  The GPL is known to
> cause problems with Haskell code due to cross module inlining.  I
> don't know how the "A" in AGPL changes things.
>

I understand your point. I didn't know the problems with cross module
inlining that Haskell suffers. I learned the BSD3, I think is a good  and
I'll change it on github and I'll put in the next release.


>  * Some of the exposed function names have been changed from the
> original name in the OpenCL specification.  This is the same thing
> that was done with the OpenGL bindings and it is very confusing for
> people who come to the Haskell bindings from the official
> documentation.  I realize that some of the API functions require some
> bit of name mangling, but I think the current way is not the right
> way.  For example with this function:
>
> http://www.khronos.org/registry/cl/sdk/1.0/docs/man/xhtml/clGetDeviceInfo.html


I use the pattern get[Type]Info -> to get[Type][specificInfo] where
specificInfo is the OpenCL name of an enumerate. I don't know if your
proposal, I open a ticket on github to think about.


> We could have a different version of the function for each return
> type, clGetDeviceInfo_FPConfig, clGetDeviceInfo_AddressBits, etc.
> It's a great naming convention but it has the property that someone
> searching the bindings or the bindings' haddocks for clGetDeviceInfo
> will find those functions.  I think this is better than naming it
> clGetDeviceExtensions, which is not in the OpenCL specification.
>
> I'd still be willing to test the changes you have, I just don't want
> to contribute to your bindings due to the license.  I currently
> thinking of starting my own bindings (Jeff's bindings contain too many
> small bugs and if I'm going to change most lines of code then I might
> as well start from scratch so that it can have a standard BSD3
> license).
>
> Jason
>
I'll change the License to BSD3, Please, keep testing the code and merge
back your changes.  I thank for your help.

Thanks for the feedback.
Luis
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Composing a list of Enumeratees into an Enumerator using ($=)

2011-10-04 Thread Román González
Hello Conrad,


Thanks for taking the time to answer back. Actually I don't want to do
anything fancy, I just want to compose a list of Enumeratees together into
an Enumerator, using the same type for both ao and ai, I suspect it doesn't
matter what the type of this ao and ai are, I would obtain the same error
using this simpler example:

module Main where

import Data.List (foldl')
import Data.Enumerator hiding (foldl')
import qualified Data.Enumerator.List as EL

-- This is what I orginally have
main :: IO ()
main = run_ (((enumList 5 [1..] $=
   EL.isolate 100) $=
   EL.filter ((== 0) . (`mod` 2))) $$
   EL.consume) >>=
   print

-- This is what I want and for some reason is not
-- compiling (infinite type error)
--main2 :: IO ()
--main2 = run (enum $$ EL.consume) >>= print
-- where
--   enum = foldl' ($=)
-- (enumList 5 [1..])
-- [ EL.isolate 100
-- , EL.filter ((==0) . (`mod` 2))
-- ]



For some complicated type logic, main2 won't compile, I'm trying to figure
out a way to actually do this. The reason why I want to do the composition
through list is because I'm mapping input parameters (from
System.Environment.getArgs) to a list of Enumeratees, and I want to compose
them dynamically.

Hope this helps.

Roman.-

2011/10/3 Conrad Parker 

> 2011/10/4 Román González :
> > Hey guys,
> >
> > Right now I'm facing with a type problem that is really nasty, I want to
> > compose a list of enumeratees using the ($=) operator to create a new
> > enumerator.  Whenever I'm trying to use the foldx function in conjunction
> > with ($=) I get this error:
> >
> >> :t foldr ($=)
> >
> > :1:7:
> > Occurs check: cannot construct the infinite type:
> >   b0 = Step ao0 m0 b0
> > Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >-> Enumeratee ao0 ao0 m0 b0
> >-> Enumeratee ao0 ao0 m0 b0
> >   Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >-> Enumeratee ao0 ao0 m0 b0
> >-> Enumerator ao0 m0 b0
> > In the first argument of `foldr', namely `($=)'
> > In the expression: foldr ($=)
> >
> >> :t Prelude.foldl ($=)
> >
> > :1:15:
> > Occurs check: cannot construct the infinite type:
> >   b0 = Step ao0 m0 b0
> > Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >-> Enumeratee ao0 ao0 m0 b0
> >-> Enumerator ao0 m0 (Step ao0 m0 b0)
> >   Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >-> Enumeratee ao0 ao0 m0 b0
> >-> Enumerator ao0 m0 b0
> > In the first argument of `Prelude.foldl', namely `($=)'
> > In the expression: Prelude.foldl ($=)
> >
> > :1:15:
> > Occurs check: cannot construct the infinite type:
> >   b0 = Step ao0 m0 b0
> > Expected type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >-> Enumeratee ao0 ao0 m0 b0
> >-> Enumerator ao0 m0 (Step ao0 m0 b0)
> >   Actual type: Enumerator ao0 m0 (Step ao0 m0 b0)
> >-> Enumeratee ao0 ao0 m0 b0
> >-> Enumerator ao0 m0 b0
> > In the first argument of `Prelude.foldl', namely `($=)'
> > In the expression: Prelude.foldl ($=)
> >
> > Obviously there is something I don't quite understand about the ($=) (=$)
> > functions, how can one compose a list of enumeratees, is it even
> possible?
>
> Hi,
>
> what are you trying to actually do, ie. what kind of data are you
> trying to transform, what are the inputs and outputs of each
> enumeratee?
>
> are you trying to feed the output of the first enumeratee into the
> input of the second, and so on? or are you trying to run them all in
> parallel?
>
> Conrad.
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe