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


[Haskell-cafe] Re: Suggestions for improvement

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

> You need a function like the following for that:
>
> comma :: (a -> b) -> (a -> c) -> a -> (b,c)
> comma f g x = (f x, g x)
>
> Then you could say:
>
> blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength
>
> Ignore this if you haven't read about Applicative or type classes yet,
> but using the Applicative instance for arrow types (->) a, you can
> also write
>
> comma = liftA2 (,)
>
> or
>
> 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

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

blowup2 :: String -> String
blowup2 = (uncurry (++)) . comma2 (blowup2 . allButLast) lastToTheLength

-- Imported Control.Applicative earlier.
comma2 :: (a -> b) -> (a -> c) -> a -> (b,c)
comma2 = liftA2 (,)

% ghci
GHCi, version 6.12.3: 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> :l Chapter01.hs 
[1 of 1] Compiling Chapter01( Chapter01.hs, interpreted )
Ok, modules loaded: Chapter01.
*Chapter01> comma1 allButLast lastToTheLength "abcd"
("abc","")
*Chapter01> comma2 allButLast lastToTheLength "abcd"
("abc","")
*Chapter01> blowup1 "abcd"
"^CInterrupted.
*Chapter01> blowup2 "abcd"
"^CInterrupted.

It looks like both the above versions of blowup go into some infinite
recursion, and have to be interrupted.

Regards,
Raghavendra.

-- 
N. Raghavendra  | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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


[Haskell-cafe] Re: Suggestions for improvement

2010-10-04 Thread N. Raghavendra
At 2010-10-05T09:21:51+13:00, Richard O'Keefe wrote:

> answer s = concat $ zipWith replicate [1..] s
>
> I looked at the examples and said, "hmm, elements are being repeated
> varying numbers of times".  Looked up "repeat", found that that was
> the wrong function, and saw "replicate", which is the right one:
>   replicate n x = [x . x] with n copies of x
> So zipWith [1..] "abcd" is ["a", "bb", "ccc", ""]
> and pasting those together is just what concat does.
>
> Had replicate, zipWith, concat not already been provided, I might
> have done one of two things.

Many thanks for the detailed explanation.  It is instructive because I
thought of a solution in a different way.  Another lesson is that I must
know the Prelude well.  I've also installed `pointfree'.  Together with
Hlint, it seems a useful tool for learning; for one thing, both of them
tell me about functions I didn't know earlier.

Regards,
Raghavendra.

-- 
N. Raghavendra  | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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


[Haskell-cafe] Re: Suggestions for improvement

2010-10-04 Thread N. Raghavendra
At 2010-10-03T20:03:22-04:00, wren ng thornton wrote:

> And just to play a little Haskell golf:
>
> lastToTheLength = ap (flip map) (const . last)

Thanks for that.

Regards,
Raghavendra.

-- 
N. Raghavendra  | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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


[Haskell-cafe] Re: Suggestions for improvement

2010-10-04 Thread N. Raghavendra
At 2010-10-04T01:52:05+04:00, Victor Nazarov wrote:

> I suggest to pay more attention to haskell's standard library.
>
> "allButLast" is called "init" in Data.List module.

Thanks for that.   I should keep printouts of the Prelude handy.

> Second, do not use explicit recursion. You can capture recursion using
> some high-order function like map, filter, foldr and so on:
>
> lastToTheLength xs = map f xs
>   where f = const . last $ xs
>
> And last, your type signatures are too restrictive. You can apply your
> functions to arbitrary lists.
>
> lastToTheLength :: [a] -> [a]
>
> Standard library knowledge is very helpful in producing short and
> clear definitions.
>
> blowup = concat . zipWith replicate [1..]

That looks neat!  Many thanks for the detailed remarks.

Regards,
Raghavendra.

-- 
N. Raghavendra  | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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


[Haskell-cafe] Re: Suggestions for improvement

2010-10-04 Thread N. Raghavendra
At 2010-10-03T13:49:34-07:00, Gregory Crosswhite wrote:

> It is worth noting that such a function already exists in the standard
> libraries;  it is the &&& operator in Control.Arrow:
>
> blowup = uncurry (++) . (blowup . allButLast &&& lastToTheLength)

Thanks for that.  More reading material!

Regards,
Raghavendra.

-- 
N. Raghavendra  | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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


[Haskell-cafe] Re: Suggestions for improvement

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

> Additionally, you can't combine the functions (blowup . allButLast)
> and lastToTheLength into a function that returns a pair like you seem
> to attempt. You need a function like the following for that:
>
> comma :: (a -> b) -> (a -> c) -> a -> (b,c)
> comma f g x = (f x, g x)
>
> Then you could say:
>
> blowup = (uncurry (++)) . comma (blowup . allButLast) lastToTheLength

Thanks, I'll try that.

> Ignore this if you haven't read about Applicative or type classes yet,
> but using the Applicative instance for arrow types (->) a, you can
> also write
>
> comma = liftA2 (,)

I hadn't come up to that point, but will read about it now.

Regards,
Raghavendra.

-- 
N. Raghavendra  | http://www.retrotexts.net/
Harish-Chandra Research Institute   | http://www.mri.ernet.in/
See message headers for contact and OpenPGP information.

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