Re: Re[2]: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Dean Herington & Elizabeth Lacey

At 3:36 AM -0600 10/5/10, Luke Palmer wrote:

On Mon, Oct 4, 2010 at 9:04 PM, Dean Herington
 wrote:

 With respect to "datatype destructing" functions, the Prelude has:

 maybe :: b -> (a -> b) -> Maybe a -> b
 either :: (a -> c) -> (b -> c) -> Either a b -> c

 which suggests the following signatures for the analogues for Bool and list
 types:

 bool :: a -> a -> Bool -> a
 list :: b -> (a -> [a] -> b) -> [a] -> b


This suggestion is not so clear to me.  Maybe and Either are both
non-recursive, so the Church and Scott encodings coincide.  You've
written the Scott encoding of list.  The Church encoding should look
familiar:

list :: b -> (a -> b -> b) -> [a] -> b

Intuitively, a Scott encoding peels off one layer of datatype, whereas
a Church encoding flattens down a whole recursive structure.  Church
encodings are more powerful -- you can do more without requiring a
fixed point operator.

Just to be clear, I am not arguing anything other than "maybe" and
"either" don't readily generalize to "list" because of list's
recursiveness.

Luke


Thanks, Luke, for pointing out the Church vs. Scott encoding issue. 
I agree with your conclusion (and feel better about the lack of the 
version of "list" I had suggested).


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


Re: [Haskell-cafe] Big Arrays

2010-10-05 Thread Hemanth Kapila
Thanks Ketil.
On Wed, Oct 6, 2010 at 1:36 AM, Ketil Malde  wrote:

> > Just out of curiosity, may I know a use case of such huge arrays?
>
> Bloom filters?
>
> Am probably dense - I still did not get an idea of where would one use such
a big array.

Let us say, we are using a bit-array of size 2^43 (that is, a byte array of
size 2^40) to store a bloom filter. And let us further assume that we are
interested in a false-positive probability of 0.01

That means, I will be able to use this array to represent  a set of
cardinality 9.18e11 ~ 10^12

I was curious to know what sort of programs would be dealing with sets of
10^12 elements.
Am mainly curious about how one would decide that bloom filters are the best
algorithm when dealing with this amount of data.What factors do we consider
when deciding the algorithm or the data structure?  The impact on GC would
be taken into account, for example (am guessing there would be at least one
copy from a younger generation to a permanent generation)?


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


[Haskell-cafe] Re: Haskell Platform: failed to parse output of 'ghc-pkg dump'

2010-10-05 Thread Tom Hawkins
Classic pilot error.  I had an old cabal.exe on the search path.

-Tom

On Tue, Oct 5, 2010 at 8:09 PM, Tom Hawkins  wrote:
> I'm having trouble installing Haskell Platform on Windows.  After the
> install, I run "cabal update", which appears to work: 00-index.tar.gz
> is deposited in C:/Documents and Settings//Application
> Data/cabal/packages/hackage.haskell.org.  However, when I try to
> "cabal install" anything, I get:
>
> cabal.exe: failed to parse output of 'ghc-pkg dump'
>
> "ghc-pkg dump --global" appears to run just fine.
>
> Ideas?  Suggestions?
>
> -Tom
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Platform: failed to parse output of 'ghc-pkg dump'

2010-10-05 Thread Tom Hawkins
I'm having trouble installing Haskell Platform on Windows.  After the
install, I run "cabal update", which appears to work: 00-index.tar.gz
is deposited in C:/Documents and Settings//Application
Data/cabal/packages/hackage.haskell.org.  However, when I try to
"cabal install" anything, I get:

cabal.exe: failed to parse output of 'ghc-pkg dump'

"ghc-pkg dump --global" appears to run just fine.

Ideas?  Suggestions?

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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Evan Laforge
-1 for if then.  The examples of "curried" if then else look, to my
eyes, less readable than the pointed version.  And it's easy enough to
write a 'bool' deconstructor, or an 'ifM' for the monadic case.

+1 for something to solve the "dummy <- m; case dummy of" problem.
Here are the possibilities I can think of:

1) case of:

m >>= case of
Just _ <- z | guard -> a
_ -> b

2) habit's case<-

case<- m of
Just _ <- z | guard -> a
_ -> b

3) extended lambda (not sure what this would look like... would the
below parse with the give layout?)

m >>= \
Just _ <- z | guard -> a
_ -> b

To me, #3 looks less ad-hoc and I like the idea of loosening a
restriction instead of introducing more sugar, but I'm not sure how
the syntax would work out.  Also, from another point of view, 'f x =
...' is sugared to combine a \ and a case, while \ is unsugared, so
tacking some case sugar on to \ would introduce sugar in a previously
sugar-free area.  Of course that \ is already sugared to curry
automatically, but if you rephrase this as "add more sugar" rather
than "loosen a restriction" it suddenly becomes less attractive since
now it's just sugar vs. sugar :)

#2 looks the nicest for this specific use, but seems less general than
#1.  For instance, #1 allows "f = case of { ... } . g".

So I like #1.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Richard O'Keefe

On 6/10/2010, at 5:56 AM, Brandon S Allbery KF8NH wrote:

>> In order to be consistent with current case, maybe in layout mode:
>> 
>> \1 -> f
>> 2 -> g
>> 
>> and in non-layout mode
>> 
>> \{1 -> f; 2 -> g}
> 
> +1; likewise for consistency it should support guards (which would preclude
> using | the way Richard suggested, and goes along with the "lambda-case" 
> thing).

It's not that I particularly wanted "|".
Just that I thought some sort of visual mark would be a good idea.
Forget I ever suggested it.

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


[Haskell-cafe] Re: hClose: invalid argument (Invalid or incomplete multibyte or wide character)

2010-10-05 Thread Johannes Waldmann
My application was actually running as a CGI program
and I needed some time to find out 
that I should put: SetEnv LC_ALL en_US.UTF-8
into /etc/apache2/sites-available/default 


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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Max Bolingbroke
On 4 October 2010 00:38, Conal Elliott  wrote:
> I like it!
>
> Are the other sections available as well, e.g.,
>
>     (if False then else "Cafe") "Haskell" --> "Cafe"

They are not, though this would certainly make sense for lambda-if.
It's not so clear with lambda-case because of the issue of free
variables. Potentially we could support something like this, but it's
a bit scary-looking:

(case x of Just -> ; Nothing ->) (\y -> "I'm a Just") "I'm a nothing"

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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Max Bolingbroke
On 5 October 2010 17:38, Henning Thielemann
 wrote:
> Richard O'Keefe schrieb:
>
>> I'd prefer to see something like
>>       \ 1 -> f
>>       | 2 -> g
>> but I'm sure something could be worked out.
>
> In order to be consistent with current case, maybe in layout mode:
>
> \1 -> f
>  2 -> g
>
> and in non-layout mode
>
> \{1 -> f; 2 -> g}

Duncan Coutts also suggested this possibility to me - once I saw it
actually liked it rather better than the lambda-case stuff,
particularly since it generalises nicely to multiple arguments. I may
try to write a patch for this extension instead when I get some free
time.

To those asking where lambda-if comes from: it was just something I
hacked in while I was there - I don't have a particular motivation
example. It just seemed like a natural extension of the lambda-case
idea.

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


Re: [Haskell-cafe] Re: hClose: invalid argument (Invalid or incomplete multibyte or wide character)

2010-10-05 Thread Daniel Fischer
On Wednesday 06 October 2010 00:30:31, Johannes Waldmann wrote:
> > What does locale say your locale is?
> > If it's *.UTF-8, it should work, if not, that's a likely cause.
>
> So, it was indeed  C. I switched this - what now? Recompile?
> Just my application? All of ghc? ...
>
I think that would be overkill.
As far as I know, it should now work without recompiling. Try your example 
first.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: hClose: invalid argument (Invalid or incomplete multibyte or wide character)

2010-10-05 Thread Johannes Waldmann

> What does locale say your locale is?
> If it's *.UTF-8, it should work, if not, that's a likely cause.

So, it was indeed  C. I switched this - what now? Recompile?
Just my application? All of ghc? ...


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


Re: [Haskell-cafe] hClose: invalid argument (Invalid or incomplete multibyte or wide character)

2010-10-05 Thread Daniel Fischer
On Tuesday 05 October 2010 23:34:56, Johannes Waldmann wrote:
> I have this program
>
> main =  writeFile "check.out" "?"
>
> that's u-umlaut, and the source file is utf-8-encoded
> and ghc-6.12.3 compiles it without problems but when running, I get
>
> hClose: invalid argument (Invalid or incomplete multibyte or wide
> character)
>
> (debian 5.0.6, kernel 2.6.18-6-686. I know that's somewhat dated.
> Would upgrading help?)
>
> Regards - J.W.

What does locale say your locale is?
If it's *.UTF-8, it should work, if not, that's a likely cause.

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


[Haskell-cafe] hClose: invalid argument (Invalid or incomplete multibyte or wide character)

2010-10-05 Thread Johannes Waldmann
I have this program

main =  writeFile "check.out" "ü"

that's u-umlaut, and the source file is utf-8-encoded 
and ghc-6.12.3 compiles it without problems but when running, I get

hClose: invalid argument (Invalid or incomplete multibyte or wide character)

(debian 5.0.6, kernel 2.6.18-6-686. I know that's somewhat dated.
Would upgrading help?)

Regards - J.W.



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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Donn Cave
Quoth Ketil Malde ,
...
> Just that they seem to be natural generalizations.  If it's just the
> single form of paramtrizing the condition, I think it's better served by
> a regular function, 'bool' or (??) or whatever.

Well, yes, there's some logic to that.  Like,

bool b c a = if a
then b
else c

  getArgs >>= bool (putStrLn "long") (putStrLn "short") . (> 0) . length

And I agree that's competitive with lambda-if as I understand it -
though possibly not for the same reasons.

For me, Haskell is not Lisp.  Haskell's syntax takes a different direction,
a mix of S-expression with stuff like if-then-else, and it works.  If the
lambda-if feature is actually useful in a way that takes advantage of
the strength of the if-then-else notation, then I'm all for it.

The problem is that due to the rarity of True/False as ... terminal
value of a computation (I just made that up!), neither of these
constructs is going to be worth much.  Forget about lambda-if, even
the regular function looks like hell -

 bool (putStrLn "long") (putStrLn "short") . (> 0) . length

Compared to

 \ t -> if length t > 0 then putStrLn "long" else putStrLn "short"
 
... and much more so, with less trivial examples.

In a brief survey of my own very small code base, I see only "hIsEOF"
as a place where I could really use lambda-if.  There, it would be
vastly better than a regular bool function, but that's a pretty minimal
use case.

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


Re: [Haskell-cafe] Big Arrays

2010-10-05 Thread Ketil Malde
Hemanth Kapila  writes:

> Just out of curiosity, may I know a use case of such huge arrays?

Bloom filters?

> At such sizes, I thought, the array would not have the expected array
> properties (constant access time) due to "thrashing".

Yes, but this is true for any array size, due to the cache hierarchy.
Accessing stuff in the same vector register is faster than accessing
things in L1 cache is faster than L2, then L3, then RAM, then swap (on
SSD), then (rotating) disk. :-)  Perhaps it's not /entirely/
unreasonable to consider array accesses to be log(N) cost - but I'm
fairly sure they're always faster than pointer chasing in tree
structures.

-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] Lambda-case / lambda-if

2010-10-05 Thread Ketil Malde
Donn Cave  writes:

> I think you're not the first to ask.  Just out of curiosity, or is
> there a use for these variations?

Just that they seem to be natural generalizations.  If it's just the
single form of paramtrizing the condition, I think it's better served by
a regular function, 'bool' or (??) or whatever.

> The reason for the initially proposed construct seems clear enough
> to me, it's very much like `case'.  

>   getargs >>= if then beTrue else beFalse . (==) ["-t"]

Isn't this equivalent, and only slightly more cumbersome?

  getArgs >>= case of {True -> beTrue; False -> beFalse} . (==) ["-t"]

(And of course,

  getArgs >>= case of ["-t"] -> beTrue; _ -> beFalse

is probably clearer anyway.)

-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] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Thomas DuBuisson
>  I don't have a horse in this race; but I am curious as to why
>  you wouldn't ask for `chunkOverhead = 16' as that seems to be
>  your intent as well as what the expression works out to on any
>  machine in common use.

Sorry, after I sent my long explanation I see what you are really
asking.  I was going by the assumption that someone really did measure
and find out that keeping the length and pointer information in the
same page as the bytestring data is a significant win.  While saying
"chunkOverhead = 16" would still work it's simply false for imaginary
128bit Haskell machines (Cell SPEs?), and I don't like betting against
commercial changes in computing.

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


[Haskell-cafe] darcs hacking sprint 15-17 Oct, Orleans

2010-10-05 Thread Eric Kow
Hi everybody,

Just a quick reminder that the fifth Darcs hacking sprint is taking
place in just ten days (Orleans, France, 15-17 Oct):

http://wiki.darcs.net/Sprints/2010-10

It's still possible to attend, but you should contact Florent Becker
(CC'ed) as soon as possible to confirm there are still spaces.

Hope to see you there!

-- 
Eric Kow 
For a faster response, try +44 (0)1273 64 2905 or
xmpp:ko...@jabber.fr (Jabber or Google Talk only)


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


Re: [Haskell-cafe] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Thomas DuBuisson
>  I don't have a horse in this race; but I am curious as to why
>  you wouldn't ask for `chunkOverhead = 16' as that seems to be
>  your intent as well as what the expression works out to on any
>  machine in common use.

To avoid copying data when perform FFI calls to common cipher routines
(such operations usually work on 128 bit blocks).

If you have a Haskell program performing full disk encryption (FDE)
then its reasonable to expect large amounts of data to need
encrypted/decrypted.  Reading in Lazy ByteStrings you get 32k -
chunkOverhead sized strict bytestrings, which is a 64 bit multiple on
32 bit machines.  IOW, for an operation like "cbc key iv lazyBS" you
will 1) encrypt 32K-16B 2) copy the remainder (8 bytes) and the next
chunk (32K - 8B) into a new strict bytestring 3) encrypt the full 32K
chunk 4) repeat.

There are other ways to do it, but the fastest ways involve making
your delicate and extremely security sensitive cipher algorithm work
on partial blocks or build the notion of linked lists of buffers (lazy
byte strings) into the implementation (which is often in C).

Unfortunately, this problem only gets worse as you expand your scope.
Hash algorithms have a much wider array of block sizes (512 to 1024
bits are very common) and we don't want to waste 1024 - 64 bits per
32KB chunk, so I didn't request that.  In situations where people know
they'll be hashing large files and explicitly use Lazy ByteStrings
they could use hGetN to set the chunk size to something agreeable.

A less programmer-intensive solution would be to have chunks at a full
32K.  I'm not sure how much of a performance problem this would
introduce (to all users of bytestrings) due to caching (other
issues?).  Did anyone measured it when the initial implementation
decided to do it this way?

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


Re: [Haskell-cafe] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Jason Dusek
On Tue, Oct 5, 2010 at 18:07, Thomas DuBuisson
 wrote:
> If not, perhaps we could make "chunkOverhead = max 16 (2 *
> sizeOf (undefined ::Int))" so it will be the same on 64 and 32
> bit systems (a 128 bit boundary, nice and fast for most modern
> cipher algorithms, sadly asking for it to match hash block
> sizes is a bit much).

  I don't have a horse in this race; but I am curious as to why
  you wouldn't ask for `chunkOverhead = 16' as that seems to be
  your intent as well as what the expression works out to on any
  machine in common use.

--
Jason Dusek
Linux User #510144 | http://counter.li.org/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ByteString missing rewrite RULES (zipWith' f a = pack . zipWith f a)

2010-10-05 Thread Thomas DuBuisson
All,

(I notice ByteString still isn't under l...@h.o ownership, which is good
because this way I can avoid the bureaucracy and e-mail the
maintainers directly)

The following is a Data.ByteString comment for the (non-exported)
function zipWith'
--
-- | (...) Rewrite rules
-- are used to automatically covert zipWith into zipWith' when a pack is
-- performed on the result of zipWith.
--

This implies there should be a rule:
{-# RULES
"ByteString specialise zipWith'" forall (f :: Word8 -> Word8 -> Word8) p q .
zipWith' f p q = pack (zipWith f p q)
  #-}

But no such rule exists in the ByteString source (the inverse rule
using 'unpack' does exist).

1) Is this an omission?  Can we fix it?  It's a rather important rule
for crypto-api.
2) Can we export zipWith' so people can be explicit?  If not, can we
get the comment about the rule placed somewhere so it will make its
way to the generated Haddock documentation for general users?

3) Very different issue:
Could .Lazy export hGetN or have defaultChunkSize configurable by a
CPP/compile time macro?

If not, perhaps we could make "chunkOverhead = max 16 (2 * sizeOf
(undefined ::Int))" so it will be the same on 64 and 32 bit systems (a
128 bit boundary, nice and fast for most modern cipher algorithms,
sadly asking for it to match hash block sizes is a bit much).

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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 10/5/10 12:38 , Henning Thielemann wrote:
> In order to be consistent with current case, maybe in layout mode:
> 
> \1 -> f
>  2 -> g
> 
> and in non-layout mode
> 
> \{1 -> f; 2 -> g}

+1; likewise for consistency it should support guards (which would preclude
using | the way Richard suggested, and goes along with the "lambda-case" thing).

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkyrWNIACgkQIn7hlCsL25WPLwCfYGc4KUscdpv3lJ7lQbugtbIa
jz4An2mbZdJr3LZY6rF0qZjBcle4HLsX
=kR9R
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread Stephen Tetley
Hi John

For the user level stuff, I don't think CSound really has "functions"
- either for the score or orchestra. The score I think is just a list
of /notes/ with many, many parameters and the orchestra is a graph
description saying how the UGens are connected.

This is good news - I believe Pan, Feldspar, Lava etc. generate
functions or procedures in the output code which means they have to
involve the complicated techniques for embedding lambdas and functions
in the EDSL. If they didn't, there would be massive code blow up.
However because CSound is more or less "straight line" code - i.e.
lines are interpreted sequentially, there are no procedures or
functions to define and call - generating it should be much simpler.

Andy Gill's Dot package on Hackage has a crafty, but simple technique
to allow you to reference graph nodes and link them within a monad and
output as "foreign" code - here dot files. Something similar might be
satisfactory for orchestra files.


Of course if you want to generate UGens in C things get complicated
again, but you still might be able to generate UGens as single
monolithic functions. I think Roger Dannenberg's Nyquist generates
UGens in this way from a Scheme like macro language, but its a long
time since I looked at it.

Best wishes

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


Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 10/5/10 10:52 , C K Kashyap wrote:
> And I had built up this impression that laziness distinguished Haskell
> by a huge margin ... but it seems that is not the case.
> Hence the disappointment.

Haskell is lazy-by-default and designed around lazy evaluation, whereas most
other languages are strict by default, designed around strictness, and make
you do extra work to get laziness which you then may lose rather easily.
Sometimes it's as easy as using an iterator, other times it means passing
around closures and invoking them at just the right time.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkyrVcgACgkQIn7hlCsL25W5tQCeMoY6XCcDLKFh3tbwdrliQSqd
grcAnjCGqxBwRsEoI2pG3+ZgA4biSDAw
=kgwK
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Henning Thielemann
Richard O'Keefe schrieb:

> I'd prefer to see something like
>   \ 1 -> f
>   | 2 -> g
> but I'm sure something could be worked out.

In order to be consistent with current case, maybe in layout mode:

\1 -> f
 2 -> g

and in non-layout mode

\{1 -> f; 2 -> g}

?

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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread John Lato
Thanks for these, and also Stephen's extensive list.  I think it's fair to
say that I'm just exploring the space and don't know what I'm doing yet.  As
such, I'm pretty open to exploring ideas.  I'm only familiar with a small
fraction of these, so I've got some reading to do now!

For my toy language I've been working on a csound-like DSP language which is
compiled to Csound code (I am slightly familiar with Atom, and moreso with
Feldspar, but they're both quite different in usage style from what I'm
aiming at).  Essentially the Csound module from Haskore, but less verbose
and typed.  I've implemented it in a final-tagless style (at least as far as
I understand Kiselyov, Carette, and Shan), which has the very nice benefit
that even though I'm currently targetting csound I could target other
languages relatively simply.

When I said I wanted to use functions from Data.List and Control.Monad, I
meant that I wanted to use them to manipulate expressions in the edsl, which
has worked very well so far.  In fact everything has worked so well, and has
been so simple to implement, that I figure I must be missing something
important.

John

On Tue, Oct 5, 2010 at 4:29 PM, Sterling Clover  wrote:

> Stephen's list is great! Two more points of reference from the recent ICFP
> -- Geoff Mainland's Nikola [1], and a nice talk on Kansas Lava [2].
>
> [1] http://www.eecs.harvard.edu/~mainland/publications/
> [2] http://www.scribd.com/doc/38559736/kansaslava-hiw10 -- hopefully the
> video from the implementor's workshop to appear soon.
>
> I suspect however, that it will prove hard to impossible to reuse Data.List
> and Control.Monad functions directly. You don't want to invoke functions at
> compile time, but represent invocations.
>
> Cheers,
> Sterl.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread steffen
Don't be to disappointed. One can always kinda fake lazy evaluation
using mutable cells.
But not that elegantly. In the example given above, all being used is
iterators as streams... this can also be expressed using lazy lists,
true. But one big difference between e.g. lazy lists and iterators is,
that lazy values are (operationally) replaced by their result wheres
values generated from iterators and streams are not.

For example one can use Iterators and chain them together in Java, to
achieve more or less the same space and runtime-efficiency found by
Stream-fusion in haskell (the Java JIT can abstract loads away, once
the iterators are build together). But If you need to access the
iterator's values more then once, you have to either force the full
iterator into a list or rerun/reevaluate the iterator every time you
need a value.

Lazy lists are nice, but haskell's laziness is not about lazy lists
only. For example lazy evaluation also matters when  creating
"elegant" Embedded DSLs... have you ever tried to build a more complex
EDSL without laziness and macros?

On 5 Okt., 16:52, C K Kashyap  wrote:
> > Yes. It would slightly easier in, say,  C# or C++.
> > I think 'D' achieves its implementation of the 'lazy' keyword using a
> > similar approach.
> > But I did not understand why you are disappointed ?
>
> The disappointment was not on a serious note ... the thing is, I
> constantly run into discussions
> about "why fp" with my colleagues - in a few of such discussions, I
> had mentioned that Haskell is the
> only well known language with lazy evaluation (IIRC, I read it
> somewhere or heard it in one of the videos)
>
> And I had built up this impression that laziness distinguished Haskell
> by a huge margin ... but it seems that is not the case.
> Hence the disappointment.
>
> --
> Regards,
> Kashyap
> ___
> Haskell-Cafe mailing list
> haskell-c...@haskell.orghttp://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] Lambda-case / lambda-if

2010-10-05 Thread Ozgur Akgun
For what it's worth, after all this discussion my rather cheeky preference
is as follows:

Instead of introducing more specialised syntax, remove both existing special
syntaxes for if and case, and introduce multi-clause support for lambdas!

Cheers!

On 2 October 2010 19:23, Max Bolingbroke  wrote:

> Hi Cafe,
>
> I implemented the proposed Haskell' feature lambda-case/lambda-if [1]
> during the Haskell Implementors Workshop yesterday for a bit of fun.
> The patches are online [2, 3].
>
> The feature is demonstrated in this GHCi session:
>
> $ inplace/bin/ghc-stage2 --interactive -XLambdaCase
> GHCi, version 7.1.20101002: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer-gmp ... linking ... done.
> Loading package base ... linking ... done.
> Loading package ffi-1.0 ... linking ... done.
> Prelude> (if then "Haskell" else "Cafe") False
> "Cafe"
> Prelude> (case of 1 -> "One"; _ -> "Not-one") 1
> "One"
> Prelude> :q
>
> Do you like this feature and think it would be worth incorporating
> this into GHC? Or is it too specialised to be of use? If there is
> enough support, I'll create a ticket and see what GHC HQ make of it.
>
> Max
>
> [1] http://hackage.haskell.org/trac/haskell-prime/ticket/41
> [2] http://www.omega-prime.co.uk/files/LambdaCase-Testsuite.patch
> [3] http://www.omega-prime.co.uk/files/LambdaCase-Compiler.patch
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Gábor Lehel
I also vote +1 for lambda-case, and abstain for lambda-if.

I don't think multiple-clause lambdas being desirable should be an
argument against lambda-case. After all, we can also define top-level
functions with either multiple clauses or a single case expression.
Haskell has always followed the TMTOWTDI school of thought with
regards to syntax, as far as I know. And lambda-case has the notable
advantage that someone has gone and implemented it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread Sterling Clover
Stephen's list is great! Two more points of reference from the recent ICFP -- 
Geoff Mainland's Nikola [1], and a nice talk on Kansas Lava [2].

[1] http://www.eecs.harvard.edu/~mainland/publications/
[2] http://www.scribd.com/doc/38559736/kansaslava-hiw10 -- hopefully the video 
from the implementor's workshop to appear soon.

I suspect however, that it will prove hard to impossible to reuse Data.List and 
Control.Monad functions directly. You don't want to invoke functions at compile 
time, but represent invocations. 

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


[Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Ertugrul Soeylemez
C K Kashyap  wrote:

> > Yes. It would slightly easier in, say,  C# or C++.
> > I think 'D' achieves its implementation of the 'lazy' keyword using
> > a similar approach.
> > But I did not understand why you are disappointed ?
>
> The disappointment was not on a serious note ... the thing is, I
> constantly run into discussions about "why fp" with my colleagues - in
> a few of such discussions, I had mentioned that Haskell is the only
> well known language with lazy evaluation (IIRC, I read it somewhere or
> heard it in one of the videos)
>
> And I had built up this impression that laziness distinguished Haskell
> by a huge margin ... but it seems that is not the case.
> Hence the disappointment.

Don't be disappointed.  There are some things, which are extremely
elegant to express with laziness:

  isPrime :: Integral a => a -> Bool
  isPrime n =
all (\x -> mod n x /= 0) . takeWhile (\x -> x*x <= n) $ primes

  primes :: Integral a => [a]
  primes = 2 : filter isPrime [3..]

These two definitions use each other in a way, which is very difficult
to express without lazy evaluation.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/


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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread Stephen Tetley
Hello John

If you are wanting variables, lambdas ... it sounds like you might be
"off-shoring" - i.e. building a little language within Haskell that is
executed on something else GPU (compiled to CUDA), compiled to C,
compiled to VHDL, etc.

Generally this is a "deep-embedding" as you need to produce output
code for the target system.

There are many papers on this - as for a survey of techniques there is
one by Keon Claessen and Gordon Pace that gives an (albeit brief)
comparison of shallow and deep embedding for Hardware EDSLs -
"Embedded Hardware Description Languages: Exploring the Design Space".
Also, the recent Kansas Lava combines a shallow embedding and a deep
embedding so it can "run" in Haskell but compile to Verilog or
VHDL(?). Andy Gill and colleagues have various papers describing its
design.

Robert Atkey and co-authors had a paper at the 2009 Haskell Symposium
"Unembedding domain-specific languages".

Conal Elliott's Pan was one of the first Haskell offshore DSLs (maybe
the first?), there is a paper "Compiling Embedded Languages" written
with Sigborn Finne and Oege de Moor. The authors acknowledge Samuel
Kamin's previous work in ML. Later Conal Elliott had a paper
describing Vertigo on GPUs.

Quite a few papers have popped up recently about off-shoring "subsets"
of Haskell to GPUs, see Joel Svensson's Obsidian and GPUgen by Manuel
M. T. Chakravarty and colleagues.

Oleg Kiselyov, Jacques Carette and Chung-chieh Shan have papers
describing embedded DSLs in the "tagless" style. There are also papers
by Jacques Carette and Oleg Kiselyov describing deep embedding in
Ocaml - I think they coined the term "off-shoring", here's one:

http://www.cas.mcmaster.ca/~carette/publications/scp_metamonads.pdf
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread C K Kashyap
>
> Yes. It would slightly easier in, say,  C# or C++.
> I think 'D' achieves its implementation of the 'lazy' keyword using a
> similar approach.
> But I did not understand why you are disappointed ?

The disappointment was not on a serious note ... the thing is, I
constantly run into discussions
about "why fp" with my colleagues - in a few of such discussions, I
had mentioned that Haskell is the
only well known language with lazy evaluation (IIRC, I read it
somewhere or heard it in one of the videos)

And I had built up this impression that laziness distinguished Haskell
by a huge margin ... but it seems that is not the case.
Hence the disappointment.


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


Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Hemanth Kapila
>
> I see ... I think I understand now.
> hmmm ... I am little disappointed though - does that mean that "all
> the laziness" cool stuffs can actually be done using
> iterators(generators)?
> As in, but for the inconvenient syntax, you can do it all in - say java?


Yes. It would slightly easier in, say,  C# or C++.
I think 'D' achieves its implementation of the 'lazy' keyword using a
similar approach.

But I did not understand why you are disappointed ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Brent Yorgey
On Tue, Oct 05, 2010 at 07:37:32PM +0530, C K Kashyap wrote:
> > Hi,
> > Let us try to rewrite the code in a more java-esque syntax:
> > It translates to something like the below generic method. Correct?
> > static  T function(IBoundsCheck within, Delta eps,  Iterator
> > iterator, T initValue){
> >       T currVal = initVal;
> >     while(iterator.hasNext()){
> >         T nextVal = iterator.next();
> >          if(within.verify(delta, eps, currVal, nextVal))
> >                           return currVal;
> >          currVal = nextVal
> >    }
> > }
> >
> > I have not tested it but I think this is a fair translation of the code.
> >  (For instance, by using an appropriate implementation of IBoundsCheck, I
> > will be able to implement the 'relativeSqrt' functionality of the example).
> > But this IS still a lazy evaluation. By passing an iterator instead of a
> > list as the third argument of the static method, I achieved 'laziness'.
> > In the example, the laziness is in the way we are iterating over the
> > sequence of values [a0,f(a0), f(f(a0)),...] and so on and not on when the
> > runtime evaluates appropriate values.
> > Just that having to write,
> > (repeat (next N) a0)
> > is (take 1000 (repeat 1)) times more intuitive and convenient than having to
> > implement the Iterator for T or implementing a true-while loop.
> >
> I see ... I think I understand now.
> hmmm ... I am little disappointed though - does that mean that "all
> the laziness" cool stuffs can actually be done using
> iterators(generators)?
> As in, but for the inconvenient syntax, you can do it all in - say
> java?

You can do anything in any Turing-complete language, but for the
inconvenient syntax.  So what?

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


Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread C K Kashyap
> Hi,
> Let us try to rewrite the code in a more java-esque syntax:
> It translates to something like the below generic method. Correct?
> static  T function(IBoundsCheck within, Delta eps,  Iterator
> iterator, T initValue){
>       T currVal = initVal;
>     while(iterator.hasNext()){
>         T nextVal = iterator.next();
>          if(within.verify(delta, eps, currVal, nextVal))
>                           return currVal;
>          currVal = nextVal
>    }
> }
>
> I have not tested it but I think this is a fair translation of the code.
>  (For instance, by using an appropriate implementation of IBoundsCheck, I
> will be able to implement the 'relativeSqrt' functionality of the example).
> But this IS still a lazy evaluation. By passing an iterator instead of a
> list as the third argument of the static method, I achieved 'laziness'.
> In the example, the laziness is in the way we are iterating over the
> sequence of values [a0,f(a0), f(f(a0)),...] and so on and not on when the
> runtime evaluates appropriate values.
> Just that having to write,
> (repeat (next N) a0)
> is (take 1000 (repeat 1)) times more intuitive and convenient than having to
> implement the Iterator for T or implementing a true-while loop.
>
I see ... I think I understand now.
hmmm ... I am little disappointed though - does that mean that "all
the laziness" cool stuffs can actually be done using
iterators(generators)?
As in, but for the inconvenient syntax, you can do it all in - say java?

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


Re: [Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread Hemanth Kapila
Hi,

Let us try to rewrite the code in a more java-esque syntax:

It translates to something like the below generic method. Correct?

static  T function(IBoundsCheck within, Delta eps,  Iterator
iterator, T initValue){
  T currVal = initVal;
while(iterator.hasNext()){
T nextVal = iterator.next();
 if(within.verify(delta, eps, currVal, nextVal))
  return currVal;
 currVal = nextVal
   }
}


I have not tested it but I think this is a fair translation of the code.
 (For instance, by using an appropriate implementation of IBoundsCheck, I
will be able to implement the 'relativeSqrt' functionality of the example).

But this IS still a lazy evaluation. By passing an iterator instead of a
list as the third argument of the static method, I achieved 'laziness'.

In the example, the laziness is in the way we are iterating over the
sequence of values [a0,f(a0), f(f(a0)),...] and so on and not on when the
runtime evaluates appropriate values.

Just that having to write,

(repeat (next N) a0)

is (take 1000 (repeat 1)) times more intuitive and convenient than having to
implement the Iterator for T or implementing a true-while loop.


/Hemanth K



On Tue, Oct 5, 2010 at 4:50 PM, C K Kashyap  wrote:

> Hi All,
>
> I was going through the paper's "lazy evaluation" section where the
> square root example is given. It occurred to me that one could
> implement it in a modular way with just higher order functions
> (without the need for lazy evaluation that is).
>
>
> function f (within, eps, next, a0){
>   while(true){
>a1=next(a0);
>if(within(a0,a1,eps)return a0;
>   a0=a1;
>   }
> }
>
> Is this not the case?
>
> --
> Regards,
> Kashyap
> ___
> 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: Re[2]: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Nicolas Pouillard
On Tue, 5 Oct 2010 03:36:12 -0600, Luke Palmer  wrote:
> On Mon, Oct 4, 2010 at 9:04 PM, Dean Herington
>  wrote:
> > With respect to "datatype destructing" functions, the Prelude has:
> >
> > maybe :: b -> (a -> b) -> Maybe a -> b
> > either :: (a -> c) -> (b -> c) -> Either a b -> c
> >
> > which suggests the following signatures for the analogues for Bool and list
> > types:
> >
> > bool :: a -> a -> Bool -> a
> > list :: b -> (a -> [a] -> b) -> [a] -> b
> 
> This suggestion is not so clear to me.  Maybe and Either are both
> non-recursive, so the Church and Scott encodings coincide.  You've
> written the Scott encoding of list.  The Church encoding should look
> familiar:
> 
> list :: b -> (a -> b -> b) -> [a] -> b

I would argue for the previous one (Scott), since we already have this one
(this is foldr with another order for arguments).

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


Re: [Haskell-cafe] pointers for EDSL design

2010-10-05 Thread C K Kashyap
> Any advice or references would be very much appreciated.
> Best,

Please check out the EDSL around the software build domain -
* slides http://www.galois.com/~dons/talks/hiw-2010/ndm-shake.pdf
* video  http://www.vimeo.com/15465133

This one is around the music composition domain
http://www.haskell.org/haskore/onlinetutorial/index.html

I could not gather the domain you are trying to target.

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


Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Neil Brown

On 05/10/10 07:52, Nicolas Wu wrote:

I'd prefer to see something like
\ 1 ->  f
| 2 ->  g
but I'm sure something could be worked out.
 

While I think the "case of"
is a good idea, multiple clauses in lambdas seems more canonical to
me.
   


Alternatively, we could abandon lambdas and just use lambda-case.

All expressions like \1 -> f become case of 1 -> f

Multi-argument functions are a bit more verbose, as we effectively go 
back to single argument functions with manual currying:


\x (C y) -> z becomes: case of {x -> case of {C y -> z}}

There is the small matter of losing backwards compatibility, of course.  
But on the plus side, this would reduce the number of constructions in 
the language by one.  (I think the strictness semantics, etc match up 
for this transformation?).


;-)

Thanks,

Neil.

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


[Haskell-cafe] Lazy evaluation from "Why Functional programming matters"

2010-10-05 Thread C K Kashyap
Hi All,

I was going through the paper's "lazy evaluation" section where the
square root example is given. It occurred to me that one could
implement it in a modular way with just higher order functions
(without the need for lazy evaluation that is).


function f (within, eps, next, a0){
   while(true){
a1=next(a0);
if(within(a0,a1,eps)return a0;
   a0=a1;
   }
}

Is this not the case?

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


Re: Re[2]: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Luke Palmer
On Mon, Oct 4, 2010 at 9:04 PM, Dean Herington
 wrote:
> With respect to "datatype destructing" functions, the Prelude has:
>
> maybe :: b -> (a -> b) -> Maybe a -> b
> either :: (a -> c) -> (b -> c) -> Either a b -> c
>
> which suggests the following signatures for the analogues for Bool and list
> types:
>
> bool :: a -> a -> Bool -> a
> list :: b -> (a -> [a] -> b) -> [a] -> b

This suggestion is not so clear to me.  Maybe and Either are both
non-recursive, so the Church and Scott encodings coincide.  You've
written the Scott encoding of list.  The Church encoding should look
familiar:

list :: b -> (a -> b -> b) -> [a] -> b

Intuitively, a Scott encoding peels off one layer of datatype, whereas
a Church encoding flattens down a whole recursive structure.  Church
encodings are more powerful -- you can do more without requiring a
fixed point operator.

Just to be clear, I am not arguing anything other than "maybe" and
"either" don't readily generalize to "list" because of list's
recursiveness.

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


[Haskell-cafe] pointers for EDSL design

2010-10-05 Thread John Lato
Hello,

I'm working on a prototype edsl (my first one), and I was wondering if there
are any resources that discuss pros and cons of various implementation
issues?  I'm trying to decide what should be included in the edsl vs.
re-using the meta language implementations (e.g. let-binding, lambdas).
 Most of the examples I've found are for full DSL's, not EDSL's, so it's not
clear what the best approach is.  The LLVM interface is sort of close to
what I intend, except it creates a very imperative style whereas I'm aiming
for something more functional.

A little background: I decided on a dsl because I intend to make heavy use
of Haskell functions from Data.List and Control.Monad.  If I made a full DSL
I would need to re-implement much of that functionality, so I thought it
would be more sensible to use an edsl.

Any advice or references would be very much appreciated.

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


Re: [Haskell-cafe] Re: Suggestions for improvement

2010-10-05 Thread Dominique Devriese
2010/10/5 N. Raghavendra :
> At 2010-10-03T22:45:30+02:00, Dominique Devriese wrote:

>> comma :: (a -> b) -> (a -> c) -> a -> (b,c)
>> comma f g x = (f x, g x)
>>
>> comma = liftA2 (,)

>> blowup = (uncurry (++)) . liftA2 (,) (blowup . allButLast) lastToTheLength
>
> I tried both of them, but they don't seem to work:
>
>    -- Pointfree blowup.
>    blowup1 :: String -> String
>    blowup1 = (uncurry (++)) . comma1 (blowup1 . allButLast) lastToTheLength

Sorry, I didn't look in detail at your solution in my answer, just
focused on the solution, and only checked that it compiled. Your
problem is that both your blowup functions recurse infinitely on the
empty string (blowup{1,2} [] will always call blowup{1,2} [] again).
Instead of fixing it, I recommend you study one of the other solutions
proposed in this thread, since they are superior in many ways
(shorter, more elegant, more lazy, probably more efficient).

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