Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Haskell version of a Ruby verson of a Common Lisp function

10 views
Skip to first unread message

Brian Adkins

unread,
Mar 1, 2009, 12:34:23 AM3/1/09
to

Kenny Tilton posted a simple exercise on comp.lang.lisp here:

http://groups.google.com/group/comp.lang.lisp/browse_frm/thread/296ea591d79ae7f5?hl=en#

I posted a reply in Ruby:

1 PETS = [
2 [:dog, [[:blab, 12], [:glab, 17], [:cbret, 82], [:dober, 42], [:gshep, 25]]],
3 [:cat, [[:pers, 22], [:siam, 7], [:tibet, 52], [:russ, 92], [:meow, 35]]],
4 [:snake, [[:garter, 10], [:cobra, 37], [:python, 77], [:adder, 24], [:rattle, 40]]],
5 [:cow, [[:jersey, 200], [:heiffer, 300], [:moo, 400]]]
6 ]
7
8 def digest_tag_population tag_population, pick_tags, count
9 tag_population.select {|e| pick_tags.include?(e[0]) }.
10 inject([]) {|memo,obj| obj[1].each {|e| memo << [obj[0], e[0], e[1]] }; memo }.
11 sort {|a,b| b[2] <=> a[2] }[0,count].
12 sort_by {|e| [ tag_population.map{|p| p[0]}.rindex(e[0]), e[2] * -1] }
13 end
14
15 digest_tag_population(PETS, [:dog, :cat, :snake], 5)

Output:

[[:dog, :cbret, 82],
[:dog, :dober, 42],
[:cat, :russ, 92],
[:cat, :tibet, 52],
[:snake, :python, 77]]

But this seems like something very well suited to Haskell. I'm still
very much a Haskell newbie, but if anyone would post a Haskell
version, I'd be very interested in seeing how it compares to the Ruby
and Common Lisp versions.

--
Brian Adkins
http://lojic.com/

Paul Rubin

unread,
Mar 1, 2009, 1:46:10 AM3/1/09
to
Brian Adkins <lojic...@gmail.com> writes:
> But this seems like something very well suited to Haskell. I'm still
> very much a Haskell newbie, but if anyone would post a Haskell
> version, I'd be very interested in seeing how it compares to the Ruby
> and Common Lisp versions.

import Data.List
import Data.Ord
import Control.Monad

pets =
[("dog", [("blab", 12),("glab", 17),("cbret", 82),
("dober", 42),("gshep", 25)]),
("cat", [("pers", 22),("siam", 7),("tibet", 52),
("russ", 92),("meow", 35)]),
("snake", [("garter", 10),("cobra", 37),("python", 77),
("adder", 24),("rattle", 40)]),
("cow", [("jersey", 200),("heiffer", 300),("moo", 400)])]

digest_tag tag_pop pick_tags count =
let selected_pops =
[(i,(-c,b)) | (i,(a,bs)) <- zip [0..] tag_pop, a `elem` pick_tags,
(b,c) <- bs]
top_pops = sort $ take count (sortBy (comparing snd) selected_pops)
in [(fst (tag_pop !! i), b, -c) | (i, (c,b)) <- top_pops]

main = print $ digest_tag pets ["dog","cat","snake"] 5

Brian Adkins

unread,
Mar 1, 2009, 3:02:46 PM3/1/09
to

Great - thanks!

I posted it to the thread on comp.lang.lisp. I find myself drawn to
both Haskell and Lisp which are similar in some ways and quite
different in others. I can see the benefits of a richer syntax, but I
also like a more fundamental, axiomatic approach. I don't think it's
possible to have that particular cake and eat it too.

Paul Rubin

unread,
Mar 2, 2009, 10:43:11 PM3/2/09
to
Brian Adkins <lojic...@gmail.com> writes:
> I posted it to the thread on comp.lang.lisp. I find myself drawn to
> both Haskell and Lisp which are similar in some ways and quite
> different in others. I can see the benefits of a richer syntax, but I
> also like a more fundamental, axiomatic approach. I don't think it's
> possible to have that particular cake and eat it too.

If you mean S-expression syntax, there is Liskell (a Haskell
preprocessor that's more Lisp-like than Template Haskell).

FWIW, the following implementation of that function is probably closer
to the spirit of Kenny's version than the one I originally posted:

================================================================
import Data.List
import Data.Ord

pets = [("dog", [("blab", 12),("glab", 17),("cbret", 82),
("dober", 42),("gshep", 25)]),
("cat", [("pers", 22),("siam", 7),("tibet", 52),
("russ", 92),("meow", 35)]),
("snake", [("garter", 10),("cobra", 37),("python", 77),
("adder", 24),("rattle", 40)]),
("cow", [("jersey", 200),("heiffer", 300),("moo", 400)])]

digest_tag tag_pop pick_tags count =

sortBy (comparing (\(a,_)->findIndex (==a) (map fst tag_pop)))
(take count $ sortBy (flip (comparing (snd . snd)))
[(a,(b,c)) | (a,bs) <- tag_pop, a `elem` pick_tags,
(b,c) <- bs])

main = print $ digest_tag pets ["dog","cat","snake"] 5

================================================================

Output (with a manually inserted line break) is:

*Main> main
[("dog",("cbret",82)),("dog",("dober",42)),("cat",("russ",92)),
("cat",("tibet",52)),("snake",("python",77))]

Note that while this creates and prints a bunch of nested tuples, I
don't think the tuples have any storage overhead (like cons nodes in
Lisp would). I.e. think only the actual values inside the tuples are
stored in the heap, and the compiler's type inference system figures
out how to pack and unpack and print them without resorting to runtime
boxing. I may be wrong about that though.

Note also, assuming "count" is a constant like 5, the inner "sortBy"
can be linear time rather than n log n. This is because the sort
function can use a selection-based algorithm which when combined with
Haskell's lazy evaluation, only finds the 5 smallest elements without
actually sorting the whole list.

On the other hand, this version (like Kenny's, if I read his properly)
in the outer sort, repeatedly looks up each species name by linear
search in the pick_tags list.

I'm a long way from being a Haskell wizard. Maybe a real expert
can come up with a much simpler/cleaner implementation than mine.

Mark T.B. Carroll

unread,
Mar 2, 2009, 10:57:53 PM3/2/09
to
Paul Rubin <http://phr...@NOSPAM.invalid> writes:

> sortBy (comparing (\(a,_)->findIndex (==a) (map fst tag_pop)))

Cool, thanks - I'd not noticed 'comparing' before! I always would
use compare `on` instead.

Mark

Paul Rubin

unread,
Mar 2, 2009, 11:07:58 PM3/2/09
to
"Mark T.B. Carroll" <Mark.C...@Aetion.com> writes:
> > sortBy (comparing (\(a,_)->findIndex (==a) (map fst tag_pop)))
>
> Cool, thanks - I'd not noticed 'comparing' before! I always would
> use compare `on` instead.

Hmm, I guess

sortBy (comparing (\(a,_)->findIndex ((==a) . fst) tag_pop))

would avoid creating the intermediate list, though maybe the compiler
optimizes that away anyhow.

Greg Bacon

unread,
Mar 20, 2009, 10:57:35 AM3/20/09
to
Brian Adkins wrote

: [...]
: But this seems like something very well suited to Haskell. I'm still


: very much a Haskell newbie, but if anyone would post a Haskell
: version, I'd be very interested in seeing how it compares to the Ruby
: and Common Lisp versions.

Fun excercise!

> import Data.Function (on)
> import Data.List (findIndex,sortBy)
> import Data.Maybe (fromJust)
>
> type Tag = String
> type Type = String
> type Pop = Int
> type PetTags = [(Tag, [(Type, Pop)])]
> type TaggedPet = (Tag, Type, Pop)
>
> pets :: PetTags


> pets =
> [ ("dog", [ ("blab", 12)
> , ("glab", 17)
> , ("cbret", 82)
> , ("dober", 42)
> , ("gshep", 25)
> ])

> , ("cat", [ ("pers", 22)


> , ("siam", 7)
> , ("tibet", 52)
> , ("russ", 92)
> , ("meow", 35)
> ])

> , ("snake", [ ("garter", 10)


> , ("cobra", 37)
> , ("python", 77)
> , ("adder", 24)
> , ("rattle", 40)
> ])

> , ("cow", [ ("jersey", 200)


> , ("heiffer", 300)
> , ("moo", 400)
> ])
> ]
>

> digestTagPopulation :: PetTags -> [Tag] -> Pop -> [TaggedPet]
> digestTagPopulation tagPopulation pickTags count =
> sortBy (compare `on` tagPos . tag) $
> take count $ reverse $ sortBy pop $
> flatten $ filter ((`elem` pickTags) . fst) tagPopulation
> where
> tag (t,_,_) = t
>
> pop :: TaggedPet -> TaggedPet -> Ordering
> pop = compare `on` (\(_,_,p) -> p)
>
> tagPos :: Tag -> Int
> tagPos = fromJust . (flip findIndex) pickTags . (==)
>
> flatten :: PetTags -> [TaggedPet]
> flatten = concatMap $
> \(t, subs) -> map (\(typ,p) -> (t,typ,p)) subs
>
> test :: [TaggedPet]
> test = digestTagPopulation pets ["dog","cat","snake"] 5

Ken proposed this as a test of mastery, so I'm not sure how strict
his rules are. What does it mean to write it "in one go"? Does
it have to typecheck the first time through? Is looking up types
of library functions fair game? Must the result be correct on
the first run? If yes for any, I flunked.

I welcome suggestions for improvement!

Greg
--
Human ingenuity, not government, solves the problem of scarcity. The
nations in which poverty is greatest are those that restrain human
ingenuity -- that is, freedom -- and punish initiative.
-- Wendy McElroy

Florian Kreidler

unread,
Mar 20, 2009, 1:29:36 PM3/20/09
to
Greg Bacon <gba...@hiwaay.net> schrieb:

> Brian Adkins wrote
>
>: [...]
>: But this seems like something very well suited to Haskell. I'm still
>: very much a Haskell newbie, but if anyone would post a Haskell
>: version, I'd be very interested in seeing how it compares to the Ruby
>: and Common Lisp versions.
>
> Fun excercise!
>
>> import Data.Function (on)
>> import Data.List (findIndex,sortBy)
>> import Data.Maybe (fromJust)
>>
>> type Tag = String
>> type Type = String
>> type Pop = Int
>> type PetTags = [(Tag, [(Type, Pop)])]
>> type TaggedPet = (Tag, Type, Pop)

>> digestTagPopulation :: PetTags -> [Tag] -> Pop -> [TaggedPet]


>> digestTagPopulation tagPopulation pickTags count =
>> sortBy (compare `on` tagPos . tag) $
>> take count $ reverse $ sortBy pop $
>> flatten $ filter ((`elem` pickTags) . fst) tagPopulation
>> where
>> tag (t,_,_) = t
>>
>> pop :: TaggedPet -> TaggedPet -> Ordering
>> pop = compare `on` (\(_,_,p) -> p)

If you flip function pop, then you won't need to reverse the sorted list.

>> tagPos :: Tag -> Int
>> tagPos = fromJust . (flip findIndex) pickTags . (==)

This can be restated as
tagPos = fromJust . flip elemIndex pickTags

You can exploit the monotonicity of fromJust and write
tagPos = flip elemIndex pickTags

>> flatten :: PetTags -> [TaggedPet]
>> flatten = concatMap $
>> \(t, subs) -> map (\(typ,p) -> (t,typ,p)) subs

This together with the filter would make a nice list comprehension.

>> test :: [TaggedPet]
>> test = digestTagPopulation pets ["dog","cat","snake"] 5

> I welcome suggestions for improvement!

import Data.List (sortBy, elemIndex)
import Data.Ord(comparing)

type Tag = String
type Pet = (String, Int)
type PetTag = (Tag, [Pet])
type TaggedPet = (Tag, Pet)

digestTagPopulation :: [PetTag] -> [Tag] -> Int -> [TaggedPet]
digestTagPopulation tp tags c
= sortBy (comparing $ flip elemIndex tags . fst) $
take c $ sortBy (flip $ comparing $ snd . snd)
[ (t, p) | (t, ps) <- tp, t `elem` tags, p <- ps ]

Florian Kreidler

unread,
Mar 22, 2009, 8:19:13 AM3/22/09
to
Florian Kreidler <m...@privacy.net> schrieb:

> import Data.List (sortBy, elemIndex)
> import Data.Ord(comparing)
>
> type Tag = String
> type Pet = (String, Int)
> type PetTag = (Tag, [Pet])
> type TaggedPet = (Tag, Pet)
>
> digestTagPopulation :: [PetTag] -> [Tag] -> Int -> [TaggedPet]
> digestTagPopulation tp tags c
> = sortBy (comparing $ flip elemIndex tags . fst) $
> take c $ sortBy (flip $ comparing $ snd . snd)
> [ (t, p) | (t, ps) <- tp, t `elem` tags, p <- ps ]

Here is a version that uses Generalised List Comprehensions. It
also groups the resulting list by tag:

{-# LANGUAGE TransformListComp #-}
import Data.List (elemIndex)
import GHC.Exts(sortWith, the)

type PetTag = (String, [(String, Int)])

digestTagPopulation :: [PetTag] -> [String] -> Int -> [PetTag]
digestTagPopulation pettags tags count
= [ (the tag, pet) |
(tag, pets) <- pettags,
tag `elem` tags,
pet@(_, pop) <- pets,
then sortWith by - pop,
then take count,
then group by tag,
then sortWith by elemIndex (the tag) tags
]

Greg Bacon

unread,
Mar 22, 2009, 7:49:48 PM3/22/09
to
Nice! Thanks for the examples!

Greg
--
The moral of the story is that with a contrived example, you can prove
anything. Oops. No, that's not what I meant to say.
-- Joel Spolsky

0 new messages