Send Beginners mailing list submissions to
[email protected]
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
[email protected]
You can reach the person managing the list at
[email protected]
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."
Today's Topics:
1. Re: Circular Linked Lists (Dave Bayer)
2. Re: Circular Linked Lists (Daniel Fischer)
3. Re: Circular Linked Lists (Brent Yorgey)
4. Re: Circular Linked Lists (Dave Bayer)
5. Re: Circular Linked Lists (Dave Bayer)
6. Parsing a file with data divided into sections
(Patrick LeBoutillier)
7. Re: Parsing a file with data divided into sections
(Magnus Therning)
8. Re: Parsing a file with data divided into sections
(Heinrich Apfelmus)
9. Re: Re: Parsing a file with data divided into sections
(Magnus Therning)
10. Re: Re: Parsing a file with data divided into sections
(Patrick LeBoutillier)
----------------------------------------------------------------------
Message: 1
Date: Tue, 3 Feb 2009 09:54:46 -0500
From: Dave Bayer <[email protected]>
Subject: Re: [Haskell-beginners] Circular Linked Lists
To: Brent Yorgey <[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes
So the "repeat bars" are there until the first pass through the list
completes, otherwise cycle would be bottom on infinite lists.
Thereafter, you're saying that a core dump would reveal a completely
homogeneous memory representation, just like C code, that one could
pass through the foreign function interface to C code?
GHC seems to have a special awareness of cyclic lists. For example,
ghci computes
> (zip (cycle [1..3]) (cycle [1..4])) !! (1000^1000)
immediately, as if it knows enough to compute 1000^1000 mod 12, by
repeated squaring.
On Feb 3, 2009, at 9:17 AM, Brent Yorgey wrote:
> It doesn't?
>
> cycle xs = xs' where xs' = xs ++ xs'
>
> That sure looks like a cyclic data structure to me! xs' references a
> thunk which computes (xs ++ xs'); this thunk, in turn, references
> xs'. cycle is memory-efficient precisely because it *does* actually
> construct a cyclic data structure.
------------------------------
Message: 2
Date: Tue, 3 Feb 2009 16:04:11 +0100
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] Circular Linked Lists
To: Dave Bayer <[email protected]>, Brent Yorgey
<[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset="iso-8859-1"
Am Dienstag, 3. Februar 2009 15:54 schrieb Dave Bayer:
> So the "repeat bars" are there until the first pass through the list
> completes, otherwise cycle would be bottom on infinite lists.
> Thereafter, you're saying that a core dump would reveal a completely
> homogeneous memory representation, just like C code, that one could
> pass through the foreign function interface to C code?
>
> GHC seems to have a special awareness of cyclic lists. For example,
> ghci computes
>
> > (zip (cycle [1..3]) (cycle [1..4])) !! (1000^1000)
No, it's that the type of (!!) is [a] -> Int -> a, and 1000^1000 :: Int is 0.
>
> immediately, as if it knows enough to compute 1000^1000 mod 12, by
> repeated squaring.
>
> On Feb 3, 2009, at 9:17 AM, Brent Yorgey wrote:
> > It doesn't?
> >
> > cycle xs = xs' where xs' = xs ++ xs'
> >
> > That sure looks like a cyclic data structure to me! xs' references a
> > thunk which computes (xs ++ xs'); this thunk, in turn, references
> > xs'. cycle is memory-efficient precisely because it *does* actually
> > construct a cyclic data structure.
>
------------------------------
Message: 3
Date: Tue, 3 Feb 2009 10:07:50 -0500
From: Brent Yorgey <[email protected]>
Subject: Re: [Haskell-beginners] Circular Linked Lists
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii
On Tue, Feb 03, 2009 at 09:54:46AM -0500, Dave Bayer wrote:
> So the "repeat bars" are there until the first pass through the list
> completes, otherwise cycle would be bottom on infinite lists. Thereafter,
> you're saying that a core dump would reveal a completely homogeneous memory
> representation, just like C code, that one could pass through the foreign
> function interface to C code?
I'm not really sure what you mean by "repeat bars". There really is a
cyclic data structure in memory at all times--it's just that until the
first pass through the list, part of it is a thunk. After a complete
pass to the list, however, a core dump would indeed reveal something
like what you suggest.
>
> GHC seems to have a special awareness of cyclic lists. For example, ghci
> computes
>
>> (zip (cycle [1..3]) (cycle [1..4])) !! (1000^1000)
>
> immediately, as if it knows enough to compute 1000^1000 mod 12, by repeated
> squaring.
I came to the same conclusion as Daniel but it took me a few minutes
of puzzlement. Besides, it should actually be equal to (2,1), not
(1,1). =)
-Brent
------------------------------
Message: 4
Date: Tue, 3 Feb 2009 10:15:10 -0500
From: Dave Bayer <[email protected]>
Subject: Re: [Haskell-beginners] Circular Linked Lists
To: Daniel Fischer <[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes
On Feb 3, 2009, at 10:04 AM, Daniel Fischer wrote:
>> GHC seems to have a special awareness of cyclic lists. For example,
>> ghci computes
>>
>>> (zip (cycle [1..3]) (cycle [1..4])) !! (1000^1000)
>
> No, it's that the type of (!!) is [a] -> Int -> a, and 1000^1000 ::
> Int is 0.
>
>>
>> immediately, as if it knows enough to compute 1000^1000 mod 12, by
>> repeated squaring.
Thanks.
The following takes forever, but it doesn't consume memory:
> Prelude> :m Data.List
> Prelude Data.List> genericIndex (zip (cycle [1..3]) (cycle [1..4]))
> (1000^1000)
So zip is doing something smart here with cyclic lists.
------------------------------
Message: 5
Date: Tue, 3 Feb 2009 10:26:12 -0500
From: Dave Bayer <[email protected]>
Subject: Re: [Haskell-beginners] Circular Linked Lists
To: Dave Bayer <[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes
On Feb 3, 2009, at 10:15 AM, Dave Bayer wrote:
>
> The following takes forever, but it doesn't consume memory:
>
>> Prelude> :m Data.List
>> Prelude Data.List> genericIndex (zip (cycle [1..3]) (cycle [1..4]))
>> (1000^1000)
>
> So zip is doing something smart here with cyclic lists.
No, I just wasn't saving the head. This burns memory:
> Prelude Data.List> let a = zip (cycle [1..3]) (cycle [1..4])
> Prelude Data.List> head a
> (1,1)
> Prelude Data.List> genericIndex a (1000^1000)
> <interactive>: memory allocation failed (requested 2097152 bytes)
------------------------------
Message: 6
Date: Tue, 3 Feb 2009 20:58:55 -0500
From: Patrick LeBoutillier <[email protected]>
Subject: [Haskell-beginners] Parsing a file with data divided into
sections
To: beginners <[email protected]>
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
Hi all,
I wanted to parse a file that looks like this:
MONDAY
JOHN
JIM
LINDA
TUESDAY
BILL
BOB
WEDNESDAY
THURSDAY
SAM
TODD
LARRY
LUKE
FRIDAY
TED
in order to count the number of people for each day. After a (very)
long time and a lot of trial and
error, I managed to do it with this program:
import Char (isSpace)
main = interact (unlines . countSections . lines)
where countSections = map (show) . snd . foldr compileSections (0, [])
compileSections line (n, acc) =
if isSection line
then (0, (line, n) : acc)
else (n + 1, acc)
isSection line = not . isSpace . head $ line
which outputs:
("MONDAY",3)
("TUESDAY",2)
("WEDNESDAY",0)
("THURSDAY",4)
("FRIDAY",1)
I had quite a hard time figuring out how to keep count of the number
of records in each sections.
Is there a more obvious way to handle these types of problems? Are
there some builtins that could
of made it easier?
In Perl I would probably have used a hash and a variable to keep count
of the current day, incrementing
the hash value for each person until I got to the next day, but it's
not obvious to me how to transpose this
technique to functional programming.
Thanks a lot,
Patrick
--
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada
------------------------------
Message: 7
Date: Wed, 4 Feb 2009 10:02:30 +0000
From: Magnus Therning <[email protected]>
Subject: Re: [Haskell-beginners] Parsing a file with data divided into
sections
To: Patrick LeBoutillier <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=UTF-8
On Wed, Feb 4, 2009 at 1:58 AM, Patrick LeBoutillier
<[email protected]> wrote:
> Hi all,
>
> I wanted to parse a file that looks like this:
>
> MONDAY
> JOHN
> JIM
> LINDA
> TUESDAY
> BILL
> BOB
> WEDNESDAY
> THURSDAY
> SAM
> TODD
> LARRY
> LUKE
> FRIDAY
> TED
>
> in order to count the number of people for each day. After a (very)
> long time and a lot of trial and
> error, I managed to do it with this program:
>
> import Char (isSpace)
>
> main = interact (unlines . countSections . lines)
> where countSections = map (show) . snd . foldr compileSections (0, [])
> compileSections line (n, acc) =
> if isSection line
> then (0, (line, n) : acc)
> else (n + 1, acc)
> isSection line = not . isSpace . head $ line
>
> which outputs:
>
> ("MONDAY",3)
> ("TUESDAY",2)
> ("WEDNESDAY",0)
> ("THURSDAY",4)
> ("FRIDAY",1)
>
> I had quite a hard time figuring out how to keep count of the number
> of records in each sections.
> Is there a more obvious way to handle these types of problems? Are
> there some builtins that could
> of made it easier?
I think that you've pretty much used accumulators in the way they most
often are used. In many cases you don't _have_ to keep count though.
Here's one way to get the same result, but without keeping count:
countDays [] = []
countDays ls = let
day = head ls
count = length $ takeWhile (isSpace . head) $ tail ls
in (day, count) : countDays (drop (1 + count) ls)
main = interact (unlines . map show . countDays . lines)
> In Perl I would probably have used a hash and a variable to keep count
> of the current day, incrementing
> the hash value for each person until I got to the next day, but it's
> not obvious to me how to transpose this
> technique to functional programming.
Often transposing from imperative to functional isn't what you want to
do. One of the arguments for learning both imperative and functional
languages is that they approach problems differently, resulting in
different solutions. I suspect you will find Haskell, and indeed any
functional language, difficult to use if you try to "think
imperative". It takes time to learn new ways to think about problems,
but in the end you'll never look at things the same way again :-)
/M
--
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnusï¼ therningï¼org Jabber: magnusï¼ therningï¼org
http://therning.org/magnus identi.ca|twitter: magthe
------------------------------
Message: 8
Date: Wed, 04 Feb 2009 12:10:02 +0100
From: Heinrich Apfelmus <[email protected]>
Subject: [Haskell-beginners] Re: Parsing a file with data divided into
sections
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=UTF-8
Magnus Therning wrote:
> Patrick LeBoutillier wrote:
>>
>> I wanted to parse a file that looks like this:
>>
>> MONDAY
>> JOHN
>> JIM
>> LINDA
>> TUESDAY
>> BILL
>> BOB
>> WEDNESDAY
>> THURSDAY
>> SAM
>> TODD
>> LARRY
>> LUKE
>> FRIDAY
>> TED
>>
>> in order to count the number of people for each day. After a (very)
>> long time and a lot of trial and error,
>> I managed to do it with this program:
Nice program, especially your use of function composition is good style.
> I think that you've pretty much used accumulators in the way they most
> often are used. In many cases you don't _have_ to keep count though.
> Here's one way to get the same result, but without keeping count:
>
> countDays [] = []
> countDays ls = let
> day = head ls
> count = length $ takeWhile (isSpace . head) $ tail ls
> in (day, count) : countDays (drop (1 + count) ls)
>
> main = interact (unlines . map show . countDays . lines)
Here's a version using span from the Prelude:
main = interact $ unlines . map show . countDays . lines
countDays [] = []
countDays (day:xs) = (day, length people) : countDays xs'
where (people, xs') = span (isSpace . head) xs
Note that this file format is very simple and it's ok to use lines and
isSpace to parse it. But the tool of choice are parser combinators
like Text.Parsec or Text.ParserCombinators.ReadP .
--
http://apfelmus.nfshost.com
------------------------------
Message: 9
Date: Wed, 4 Feb 2009 11:43:45 +0000
From: Magnus Therning <[email protected]>
Subject: Re: [Haskell-beginners] Re: Parsing a file with data divided
into sections
To: Heinrich Apfelmus <[email protected]>
Cc: [email protected]
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=UTF-8
On Wed, Feb 4, 2009 at 11:10 AM, Heinrich Apfelmus
<[email protected]> wrote:
[..]
> Here's a version using span from the Prelude:
>
> main = interact $ unlines . map show . countDays . lines
>
> countDays [] = []
> countDays (day:xs) = (day, length people) : countDays xs'
> where (people, xs') = span (isSpace . head) xs
Ah, yes, `span` is the function I was looking for! I would have found
it if I had bothered to go to Hoogle :-(
/M
--
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnusï¼ therningï¼org Jabber: magnusï¼ therningï¼org
http://therning.org/magnus identi.ca|twitter: magthe
------------------------------
Message: 10
Date: Wed, 4 Feb 2009 09:15:03 -0500
From: Patrick LeBoutillier <[email protected]>
Subject: Re: [Haskell-beginners] Re: Parsing a file with data divided
into sections
To: beginners <[email protected]>
Message-ID:
<[email protected]>
Content-Type: text/plain; charset=ISO-8859-1
> Nice program, especially your use of function composition is good style.
Thanks, I must admit I put alot of time into refactoring it. There's so many
different ways of doing stuff (and then simplifying them) in Haskell!
>> I think that you've pretty much used accumulators in the way they most
>> often are used. In many cases you don't _have_ to keep count though.
>> Here's one way to get the same result, but without keeping count:
>>
>> countDays [] = []
>> countDays ls = let
>> day = head ls
>> count = length $ takeWhile (isSpace . head) $ tail ls
>> in (day, count) : countDays (drop (1 + count) ls)
>>
>> main = interact (unlines . map show . countDays . lines)
>
> Here's a version using span from the Prelude:
>
> main = interact $ unlines . map show . countDays . lines
>
> countDays [] = []
> countDays (day:xs) = (day, length people) : countDays xs'
> where (people, xs') = span (isSpace . head) xs
>
Both of these examples are great and exactly what I was looking for: a
different approach to the problem. I guess the step that was missing in my
"thought process" is that recursion doesn't have to imply processing the list
elements 1 by 1 (1 recursive call for each element). Of course it makes
perfect sense once you see it....
Thanks a lot to everyone, as usual the people on this list are always very
kind and helpful.
Patrick
>
> Note that this file format is very simple and it's ok to use lines and
> isSpace to parse it. But the tool of choice are parser combinators
> like Text.Parsec or Text.ParserCombinators.ReadP .
>
>
> --
> http://apfelmus.nfshost.com
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
--
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada
------------------------------
_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners
End of Beginners Digest, Vol 8, Issue 2
***************************************