Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  beginner question (Daniel Fischer)
   2. Re:  list monad question (Daniel Fischer)
   3. Re:  beginner question (Shawn Willden)
   4. Re:  list monad question (Matthias Guedemann)
   5. RE:  beginner question (Luca Ciciriello)
   6. Re:  list monad question (Colin Paul Adams)
   7. Re:  list monad question (Stephen Tetley)
   8. Re:  beginner question (Brent Yorgey)
   9. Re:  list monad question (Daniel Fischer)


----------------------------------------------------------------------

Message: 1
Date: Fri, 30 Oct 2009 15:46:33 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] beginner question
To: beginners@haskell.org
Message-ID: <200910301546.34301.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-15"

Am Freitag 30 Oktober 2009 14:40:13 schrieb Luca Ciciriello:
> Hi all.
>
> Just a very basic question.
>
>
>
> I need to write a function str2lsts :: String -> [[String]] in order to
> transorm a string like:
>
>
>
> "\"1\",\"cat\",\"dog\"§\"2\",\"duck\",\"goose\""
>
>
>
> in the list of lists:
>
>
>
> [["1","cat","dog"],["2","duck","goose"]]
>
>
>
> I've tried to mix recursion, pattern matching and list comprehension, but
> the obtained result was embarrassing complex (> 20 lines of awful code). I
> think that a more simple solution certainly exists.
>

splitOnToken :: Eq a => a -> [a] -> [[a]]
splitOnToken t xs
    = case break (== t) xs of
        (hd,tl) -> hd:case tl of
                    (_:r@(_:_)) -> splitOnToken t r
                    _ -> []

str2lsts = map (map read . splitOnToken ',') . splitOnToken '§'

if things weren't enclosed in quotation marks inside the string, it would be 
the nicer

map (splitOnToken ',') . splitOnToken '§'

, provided of course, neither ',' nor '§' are valid characters for the target 
strings.

import Text.ParserCombinators.Parsec

simple = between (char '"') (char '"') (many (staisfy (/= '"')))
-- alternative: simple = char '"' >> manyTill anyChar (char '"')

multiple = sepBy simple (char ',')

total = sepBy multiple (char '§')

str2lsts str
    = case parse total "" str of
        Left err -> error (show err)
        Right lsts -> lsts

>
>
>
> Thanks in advance for any idea.
>
>
>
> Luca




------------------------------

Message: 2
Date: Fri, 30 Oct 2009 16:03:37 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] list monad question
To: Matthias Guedemann <matthias.guedem...@ovgu.de>
Cc: beginners <beginners@haskell.org>
Message-ID: <200910301603.37963.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

Am Freitag 30 Oktober 2009 14:32:35 schrieb Matthias Guedemann:
> Hi Daniel,
>
> > That gives
> >
> > combinations n xs = foldr f [[]] (replicate n xs)
> >
> > pointfree, for extra goodness:
> >
> > -- pointfree f inline
> > combinations n xs = foldr ((. (. (:)) . flip map) . (>>=)) [[]]
> > (replicate n xs) -- eliminate xs
> > combinations n = foldr ((. (. (:)) . flip map) . (>>=)) [[]] . replicate
> > n -- completely pointfree
> > combinations = (foldr ((. (. (:)) . flip map) . (>>=)) [[]]  .) .
> > replicate
>
> thank you, looks rather strange to me but works well.

Yes :D The pointfree f is nicely obfuscated. But if your friend is a perl 
coder, he should 
be able to appreciate that.
The standard way to express f, however, is liftM2 (:), so

combinations = (foldr (liftM2 (:)) [[]] .) . replicate 
-- isn't that boring?

But earnestly, replicateM is the thing to use.

>
> regards



------------------------------

Message: 3
Date: Fri, 30 Oct 2009 09:11:48 -0600
From: Shawn Willden <shawn-hask...@willden.org>
Subject: Re: [Haskell-beginners] beginner question
To: beginners@haskell.org
Message-ID: <200910300911.48668.shawn-hask...@willden.org>
Content-Type: text/plain;  charset="utf-8"

On Friday 30 October 2009 07:40:13 am Luca Ciciriello wrote:
> I need to write a function str2lsts :: String -> [[String]] in order to
> transorm a string like:
>
> "\"1\",\"cat\",\"dog\"§\"2\",\"duck\",\"goose\""
>
> in the list of lists:
>
> [["1","cat","dog"],["2","duck","goose"]]

A variety of solutions on these blog posts, and the comments:

http://gimbo.org.uk/blog/2007/04/20/splitting-a-string-in-haskell/
http://julipedia.blogspot.com/2006/08/split-function-in-haskell.html

        Shawn.


------------------------------

Message: 4
Date: Fri, 30 Oct 2009 16:34:13 +0100
From: Matthias Guedemann <matthias.guedem...@ovgu.de>
Subject: Re: [Haskell-beginners] list monad question
To: Daniel Fischer <daniel.is.fisc...@web.de>
Cc: beginners <beginners@haskell.org>
Message-ID: <1256916789-sup-...@pc44es141.cs.uni-magdeburg.de>
Content-Type: text/plain; charset=UTF-8

> Yes :D The pointfree f is nicely obfuscated. But if your friend is a perl
> coder, he should 
> be able to appreciate that.

Honestly, he just wanted a "one-loop-using solution" and was not too interested
in anything using Haskell :-)

> The standard way to express f, however, is liftM2 (:), so
> 
> combinations = (foldr (liftM2 (:)) [[]] .) . replicate 
> -- isn't that boring?

true, it's almost readable 
At the moment trying to use pointfree is basically pointless for me, more
practice is needed.


regards
Matthias

-- 
__________________________________________________________
                                            ___  __    __
Dipl. Inf. Matthias Guedemann              / __\/ _\  /__\
Computer Systems in Engineering           / /   \ \  /_\
Otto-von-Guericke Universitaet Magdeburg / /___ _\ \//__
Tel.: 0391 / 67-19359                    \____/ \__/\__/
__________________________________________________________


------------------------------

Message: 5
Date: Fri, 30 Oct 2009 15:51:46 +0000
From: Luca Ciciriello <luca_cicirie...@hotmail.com>
Subject: RE: [Haskell-beginners] beginner question
To: <daniel.is.fisc...@web.de>, <beginners@haskell.org>
Message-ID: <snt128-w51684c7826089525c796ec9a...@phx.gbl>
Content-Type: text/plain; charset="iso-8859-1"


Thanks. 

 

import Text.ParserCombinators.Parsec 

 

simple = between (char '"') (char '"') (many (satisfy (/= '"')))


multiple = sepBy simple (char ',') 
total     = sepBy multiple (char '@') 

 

str2lsts :: String -> [[String]]
str2lsts str= case parse total "" str of
                   Left err -> error (show err)
                   Right lsts -> lsts

 

solves my problem. As you can see I've replaced '§' with '@' and now all works 
fine.

 

Luca. 
 
> From: daniel.is.fisc...@web.de
> To: beginners@haskell.org
> Subject: Re: [Haskell-beginners] beginner question
> Date: Fri, 30 Oct 2009 15:46:33 +0100
> 
> Am Freitag 30 Oktober 2009 14:40:13 schrieb Luca Ciciriello:
> > Hi all.
> >
> > Just a very basic question.
> >
> >
> >
> > I need to write a function str2lsts :: String -> [[String]] in order to
> > transorm a string like:
> >
> >
> >
> > "\"1\",\"cat\",\"dog\"§\"2\",\"duck\",\"goose\""
> >
> >
> >
> > in the list of lists:
> >
> >
> >
> > [["1","cat","dog"],["2","duck","goose"]]
> >
> >
> >
> > I've tried to mix recursion, pattern matching and list comprehension, but
> > the obtained result was embarrassing complex (> 20 lines of awful code). I
> > think that a more simple solution certainly exists.
> >
> 
> splitOnToken :: Eq a => a -> [a] -> [[a]]
> splitOnToken t xs
> = case break (== t) xs of
> (hd,tl) -> hd:case tl of
> (_:r@(_:_)) -> splitOnToken t r
> _ -> []
> 
> str2lsts = map (map read . splitOnToken ',') . splitOnToken '§'
> 
> if things weren't enclosed in quotation marks inside the string, it would be 
> the nicer
> 
> map (splitOnToken ',') . splitOnToken '§'
> 
> , provided of course, neither ',' nor '§' are valid characters for the target 
> strings.
> 
> import Text.ParserCombinators.Parsec
> 
> simple = between (char '"') (char '"') (many (staisfy (/= '"')))
> -- alternative: simple = char '"' >> manyTill anyChar (char '"')
> 
> multiple = sepBy simple (char ',')
> 
> total = sepBy multiple (char '§')
> 
> str2lsts str
> = case parse total "" str of
> Left err -> error (show err)
> Right lsts -> lsts
> 
> >
> >
> >
> > Thanks in advance for any idea.
> >
> >
> >
> > Luca
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
                                          
_________________________________________________________________
Download Messenger onto your mobile for free
http://clk.atdmt.com/UKM/go/174426567/direct/01/
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20091030/18dff5cb/attachment-0001.html

------------------------------

Message: 6
Date: Fri, 30 Oct 2009 15:55:01 +0000
From: Colin Paul Adams <co...@colina.demon.co.uk>
Subject: Re: [Haskell-beginners] list monad question
To: Matthias Guedemann <matthias.guedem...@ovgu.de>
Cc: beginners <beginners@haskell.org>
Message-ID: <m3zl78lvvu....@colina.demon.co.uk>
Content-Type: text/plain; charset=us-ascii

>>>>> "Matthias" == Matthias Guedemann <matthias.guedem...@ovgu.de> writes:

    Matthias> true, it's almost readable At the moment trying to use
    Matthias> pointfree is basically pointless for me, more practice
    Matthias> is needed.

Actually the pointless style does have a point - like all jargon, it
shows that you're a member of the club, and can look down on those who
don't understand it.

In support of this, it deliberately confuses beginners by omitting the
arguments that should be there according to the signature (this is a
principle purpose of currying, to confuse beginners :-) ).

I cheat - I use hlint, and write the pointless versions that it tells
me I should write instead of the pointed version that I write. 

Is there a "Bluffer's guide to Haskell"? 
-- 
Colin Adams
Preston Lancashire


------------------------------

Message: 7
Date: Fri, 30 Oct 2009 16:27:12 +0000
From: Stephen Tetley <stephen.tet...@gmail.com>
Subject: Re: [Haskell-beginners] list monad question
Cc: beginners <beginners@haskell.org>
Message-ID:
        <5fdc56d70910300927u53aa011leeb4884052903...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

2009/10/30 Colin Paul Adams <co...@colina.demon.co.uk>:

> Is there a "Bluffer's guide to Haskell"?

Whilst not a bluffers guide, this one contains several dozen flavours
of 'obscurantism' (** add your less pejorative term here **)

http://www.willamette.edu/~fruehr/haskell/evolution.html

Methinks your being a bit hard on the pointfree style, but it does
often diminish an _operation reading_ of the code (you can tell what
the code does from looking at it). So you either have to trust it, or
work it out to some expanded form you are happy with.

For what its worth I came up with this bit of golf which saves a few
keystrokes if you're prepare not to count the helper functions (I
consider them generally useful):


combinations :: Int -> [a] -> [[a]]
combinations = foldr (<:>) [[]] `oo` replicate

-- Helpers that I like but are not in the libraries

-- | Applicative 'cons'. Equivalent to - liftA2 (:) - but I like
having it around.
-- The monadic version is attributable to a parser library in Clean.

(<:>) :: Applicative f => f a -> f [a] -> f [a]
(<:>) a b = (:) <$> a <*> b

-- | Compose an arity 1 function and an arity 2 function.
--
-- I call this combinator 'specs' (aka glasses) due to its infix
-- appearance `oo` - I believe fans of Raymond Smullyan's
-- 'To Mock a Mockingbird' call it blackbird...

oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d
oo f g = (f .) . g

Best wishes

Stephen


------------------------------

Message: 8
Date: Fri, 30 Oct 2009 13:47:23 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] beginner question
To: beginners@haskell.org
Message-ID: <20091030174722.ga10...@seas.upenn.edu>
Content-Type: text/plain; charset=iso-8859-1

On Fri, Oct 30, 2009 at 01:40:13PM +0000, Luca Ciciriello wrote:
> 
> Hi all.
> 
> Just a very basic question.
> 
> I need to write a function str2lsts :: String -> [[String]] in order to 
> transorm a string like:
> 
> "\"1\",\"cat\",\"dog\"§\"2\",\"duck\",\"goose\""
>
> in the list of lists:
> 
> [["1","cat","dog"],["2","duck","goose"]]

Another possibility:


  import Data.List.Split  -- from the 'split' package on Hackage

  str2lsts = map (splitOn ",") . splitOn "@" . filter (/='"')


-Brent


------------------------------

Message: 9
Date: Fri, 30 Oct 2009 22:03:50 +0100
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] list monad question
To: beginners@haskell.org
Message-ID: <200910302203.50864.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Freitag 30 Oktober 2009 17:27:12 schrieb Stephen Tetley:
> 2009/10/30 Colin Paul Adams <co...@colina.demon.co.uk>:
> > Is there a "Bluffer's guide to Haskell"?
>
> Whilst not a bluffers guide, this one contains several dozen flavours
> of 'obscurantism' (** add your less pejorative term here **)
>
> http://www.willamette.edu/~fruehr/haskell/evolution.html
>
> Methinks your being a bit hard on the pointfree style, but it does
> often diminish an _operation reading_ of the code (you can tell what
> the code does from looking at it). So you either have to trust it, or
> work it out to some expanded form you are happy with.

Completely pointfree style tends to be unreadable except for the selected few.
It's fun to create pointfree versions of your functions, and you learn 
something by doing 
that, but it should appear rarely in your code.

Completely pointful style tends to be not unreadable, but often cluttered.

The most readable is usually a "partially pointfree" style. Which degree of 
pointfreeness 
is most readable depends of course on the reader, but there's a range which 
most can agree 
is good.

Function combinators and pipelines should be partially pointfree:
foo = bar . baz . hum

is better than

foo x = bar (baz (hum x))
or
foo x = bar $ baz $ hum x
or 
foo x = bar . baz . hum $ x

flurb f g = f . g . f

is better than

flurb f g = f (g (f x))

wibble f g = f &&& g >>> g *** f

is better than

wibble f g x = f &&& g >>> g *** f $ x

- but worse than

wibble f g = (f &&& g) >>> (g *** f)

because the latter doesn't require knowledge of the fixities to parse.
However,

wibble f g = (g . f) &&& (f . g)

is at least as good if you want it only for the Category (->). Whether that is 
better than

wibble f g x = (g (f x), f (g x))

depends on how familiar one is with Control.Arrow.
Writing flurb or wibble completely pointfree is a nightmare :)

Which is best:
a) incrementAll n xs = map (\x -> x+n) xs
b) incrementAll n xs = map (+n) xs
c) incrementAll n    = map (+n)
d) incrementAll      = map . (+)
?
None of them is unreadable - though d) is confusing in the first few weeks of 
Haskell - 
but b) and c) are clearly better than the other two and c) is a bit better than 
b) in my 
opinion.

Would you prefer:
a) comb         = flip (.) (flip (.)) (flip (.) (flip (.)))
b) comb         = (. flip (.)) . flip (.)
c) comb f       = (. f) . flip (.)
d) comb f g     = (. g) . f
e) comb f g x   = f x . g
f) comb f g x y = f x (g y)
?
a) is the prettiest, but honestly, I'd rather not meet it in code.
e) is best, f) is okay, d) acceptable.

>
> For what its worth I came up with this bit of golf which saves a few
> keystrokes if you're prepare not to count the helper functions

That's cheating (until they are in a library).

> (I consider them generally useful):

Yup.

>
>
> combinations :: Int -> [a] -> [[a]]
> combinations = foldr (<:>) [[]] `oo` replicate
>
> -- Helpers that I like but are not in the libraries
>
> -- | Applicative 'cons'. Equivalent to - liftA2 (:) - but I like
> having it around.
> -- The monadic version is attributable to a parser library in Clean.
>
> (<:>) :: Applicative f => f a -> f [a] -> f [a]
> (<:>) a b = (:) <$> a <*> b

I'd prefer either
(<:>) = liftA2 (:)
or
a <:> b = (:) <$> a <*> b

>
> -- | Compose an arity 1 function and an arity 2 function.
> --
> -- I call this combinator 'specs' (aka glasses) due to its infix
> -- appearance `oo` - I believe fans of Raymond Smullyan's
> -- 'To Mock a Mockingbird' call it blackbird...
>
> oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d
> oo f g = (f .) . g

This is sometimes also denoted by (.:), it has the pretty definition

(.:) = (.) . (.)

>
> Best wishes
>
> Stephen




------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 16, Issue 28
*****************************************

Reply via email to