Suggestions for improvement

I am reading the book `The Haskell Road to Math, Logic, ...". One of
the exercises in the first chapter asks for a function that maps a
string "abcd" to "abbcccdddd" and "bang!" to "baannngggg!!!!!". Since
such a function f fixes the empty word, and maps wa to
f(w)a^(length(w)+1) for any word w and any letter a, I came up with the
following solution:
-- Map "abcd" to "abbcccdddd" and "bang!" to "baannngggg!!!!!".
blowup :: String -> String
blowup [] = []
blowup x = blowup (allButLast x) ++ lastToTheLength x
-- Map "abcd" to "abc".
allButLast :: String -> String
allButLast [] = []
allButLast [x] = []
allButLast (x : xs) = x : allButLast xs
-- Map "abcd" to d^4 = "dddd".
lastToTheLength :: String -> String
lastToTheLength [] = []
lastToTheLength [x] = [x]
lastToTheLength (_ : xs) = lastToTheLength xs ++ [last xs]
One question I have is whether I can eliminate points in the above
definition of blowup, and write something like
blowup = (++) . (blowup . allButLast, lastToTheLength)
thinking of (++) as a function String x String -> String. Also, I can't
figure out whether it is possible to get a shorter solution using fold.
I have tried Hlint on my file, but it gave no suggestions.
I am sure there are better ways, and would like some pointers and any
general suggestions for improvement.
Thanks and regards,
Raghavendra.
--
N. Raghavendra

One question I have is whether I can eliminate points in the above definition of blowup, and write something like
blowup = (++) . (blowup . allButLast, lastToTheLength)
thinking of (++) as a function String x String -> String.
Actually (++) is of type String -> String -> String. When you want something of the type you mean (you normally write that as (String, String) -> String in Haskell, then you can use (uncurry (++)). 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 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
Also, I can't figure out whether it is possible to get a shorter solution using fold. I have tried Hlint on my file, but it gave no suggestions.
I am sure there are better ways, and would like some pointers and any general suggestions for improvement.
By the way, shorter is not always better. Trying to recognize abstraction patterns in your code is never a bad thing though. Dominique

On 10/3/10 1:45 PM, 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
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) Cheers, Greg

Gregory,
2010/10/3 Gregory Crosswhite
On 10/3/10 1:45 PM, 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
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)
Or you can write it as (liftA2 (,)) as I noted a few lines further in my mail ;) Dominique

On 10/3/10 2:24 PM, Dominique Devriese wrote:
Or you can write it as (liftA2 (,)) as I noted a few lines further in my mail ;)
Dominique
I know, I just mentioned it to increase awareness of the fact that the instance methods for all the classes in Control.Arrow can equivalently be interpreted as useful pre-defined combinators for ordinary functions. Cheers, Greg

I suggest to pay more attention to haskell's standard library.
"allButLast" is called "init" in Data.List module.
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..]
On Mon, Oct 4, 2010 at 1:24 AM, Dominique Devriese
Gregory,
2010/10/3 Gregory Crosswhite
: On 10/3/10 1:45 PM, 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
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)
Or you can write it as (liftA2 (,)) as I noted a few lines further in my mail ;)
Dominique _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Victor Nazarov

On 10/3/10 5:52 PM, Victor Nazarov wrote:
I suggest to pay more attention to haskell's standard library.
"allButLast" is called "init" in Data.List module.
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 just to play a little Haskell golf: lastToTheLength = ap (flip map) (const . last) -- Live well, ~wren

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

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

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

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

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","dddd")
*Chapter01> comma2 allButLast lastToTheLength "abcd"
("abc","dddd")
*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

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

On 4/10/2010, at 8:52 AM, N. Raghavendra wrote:
I am reading the book `The Haskell Road to Math, Logic, ...". One of the exercises in the first chapter asks for a function that maps a string "abcd" to "abbcccdddd" and "bang!" to "baannngggg!!!!!".
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", "dddd"] 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. (a) Write them. concat (x:xs) = x ++ concat xs concat [] = [] zipWith f (x:xs) (y:ys) = f x y : zipWith f xs ys zipWith _ _ _ = [] replicate (n+1) x = x : replicate n x replicate 0 _ = [] This is _still_ less code than the code I'm replying to, and gives you some reusable components as well. (b) I'd have generalised the function to f n [x1,...,xk] = [x1 n times, x2 n+1 times, ..., xk n+k-1 times] in order to get a clean recursion for f. answer s = f 1 s where f _ [] = [] -- list iteration f n (x:xs) = g n (f (n+1) xs) where g (n+1) s = x : g n s -- element replication g 0 s = s You can think of this by imagining the answer laid out in a triangle "abcd bcd cd d"

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", "dddd"] 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
participants (6)
-
Dominique Devriese
-
Gregory Crosswhite
-
N. Raghavendra
-
Richard O'Keefe
-
Victor Nazarov
-
wren ng thornton