[Haskell-cafe] RE: [Haskell] Re: state of HaXml?

2007-01-05 Thread Simon Marlow
[ moving to haskell-café... ]

Norman Ramsey wrote:
   There seems to be a misunderstanding here: readFile in
 itself is not the
   solution.  readFile is defined thus:
  
   readFile name=  openFile name ReadMode = hGetContents  
   and the original code was this:
  
  load fn = do handle - IO.openFile fn IO.ReadMode
   contents - IO.hGetContents handle
   IO.hClose handle
   return $ XP.xmlParse fn contents  
   Sure, you can replace the openFile/hGetContents pair by
 readFile, but the
   real problem is the presence of the hClose.  Removing that
 will solve your
   problem (but note that you now have no control over when
 the file is
   actually closed).

 Can I just leave it hanging and rely on the garbage collector to
 close it in the fullness of time?

Yes.  The problem I was alluding to arises when you have many lazilly-closed 
files, and you run into the system's open file limit because the runtime 
doesn't close them eagerly enough.  To be sure of closing the file at the right 
time, you need to force the entire file to be read (e.g. by forcing the result 
of the parse), then close the handle.

 Because of laziness, I believe there's no point in my writing the
 following:

  load fn = do handle - IO.openFile fn IO.ReadMode
   contents - IO.hGetContents handle
   let xml = XP.xmlParse fn contents
   IO.hClose handle
   return xml

 Is that correct?

Yes.

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


Re: [Haskell-cafe] Redefining superclass default methods in a subclass

2007-01-05 Thread Yitzchak Gale

Brian Hulley wrote:

...allow a superclass (or ancestor class)
method default to be redefined in a subclass.


This has been proposed several times over the
years. I remember seeing Simon PJ propose it
within the past year or two, I think.

I personally have needed this on several
occasions. So I would be very happy if
it were to be adopted.

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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Jules Bean

tphyahoo wrote:

So the core question (speaking as a perler) is how do you write

  my $s= 'abcdefg';
  $s =~ s/a/z/g;
  $s =~ s/b/y/g;
  print $s\n;

 in haskell? There are various haskell regex libraries out there,
  


But that's such a perler attitude. When all you have is a regex, 
everything looks like a s///!


This really doesn't look like much of a regex question to me. A more 
haskelly answer might be as simple as:


m 'a' = 'z'
m 'b' = 'y'
m  x  = x

test1 = map m abcdefg

...which is general in the sense that 'm' can be an arbitrary function 
from Char - Char, and avoids the 'overlapping replace' behaviour 
alluded to elsewhere in this thread, but is limited if you wanted to do 
string-based replacement.


To do string-based replacement you do have to think careful about what 
semantics you're expecting though (w.r.t. overlapping matches, repeated 
matches, priority of conflicting matches).


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


Re[4]: [Haskell-cafe] Composing functions with runST

2007-01-05 Thread Bulat Ziganshin
Hello Yitzchak,

Thursday, January 4, 2007, 4:25:06 PM, you wrote:

 The other is awkwardness in extending the capabilites
 of ST. For that, I would propose that the function unsafeRunST
 be added to the library.

 Bulat Ziganshin wrote:
 this function exists, but named unsafeIOtoST.

 That wasn't what I had in mind, because it forces the
 thread parameter to take the specific value RealWorld.

this parameter don't have any physical meaning at runtime. i still think
that it is just what you mean. what other meaning may have unsafeRunST
operation?


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Redefining superclass default methods in a subclass

2007-01-05 Thread Bulat Ziganshin
Hello Brian,

Thursday, January 4, 2007, 10:00:05 PM, you wrote:

 deeper, the programmer is burdened more and more by the need to
 cut-and-paste method definitions between instances because Haskell doesn't 
 allow a superclass (or ancestor class) method default to be redefined in a 
 subclass.

i've runned into this problem with Streams library. finally i've decided to
wrote bodies of such methods outside of class:

getLineBody :: (CharStream h) =  h - IO String
getLineBody h = do
   c - getChar
   

instance LineStream File where
  getLine = getLineBody

instance LineStream MemBuf where
  getLine = getLineBody


where File and MemBuf, of course, are CharStream instances


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Chris Kuklewicz
tphyahoo wrote:
 So the core question (speaking as a perler) is how do you write
 
   my $s= 'abcdefg';
   $s =~ s/a/z/g;
   $s =~ s/b/y/g;
   print $s\n;
 
  in haskell? There are various haskell regex libraries out there,
  including ones that advertise they are PCRE (Perl Compatible Reg Ex).
 

I updated the regex libraries for GHC 6.6. ( All the regex-* packages. )  The
old API is still supported in Text.Regex.  The old API has a replacement
function, while the new API does not have one (yet).

For simple regular expressions, where Posix and Perl agree, you can just use
Text.Regex.subRegex which comes with GHC.  In 6.6 this comes in the regex-compat
package, and which calls the regex-posix backend via the interfaces defined in
regex-base.  All of these come with GHC, since GHC needs regex support to
compile itself.

So if you do not need more syntax than POSIX regex (with back references) then

http://www.haskell.org/ghc/docs/latest/html/libraries/regex-compat/Text-Regex.html#v%3AsubRegex

works, but depends on the low performance posix-regex backend.  This will run
your example above, for instance.

Better regex searching performance can be had by using the new interface via
Text.Regex.Base with better backends and/or with Data.ByteString.  In the future
there will be Data.Sequence (of Char and perhaps Word8) support added to the
backends.

There is no updated API for performing replacements using a pluggable backend.
The design space is too large with conflicting needs to be lazy or strict, time
or space efficient, etc.  The best thing is to write the replacement function
that your application needs.  You can use the new searching API (see
micro-tutorial below) to write a replacement routine in less than a screen of 
code.

For instance, the regex-compat version of Text.Regex.subRegex is

 {- | Replaces every occurance of the given regexp with the replacement string.
 
 In the replacement string, @\\\1\@ refers to the first substring;
 @\\\2\@ to the second, etc; and @\\\0\@ to the entire match.
 @\\@ will insert a literal backslash.
 
 This is unsafe if the regex matches an empty string.
 -}
 subRegex :: Regex  -- ^ Search pattern
   - String -- ^ Input string
   - String -- ^ Replacement text
   - String -- ^ Output string
 subRegex _  _ = 
 subRegex regexp inp repl =
 let bre = mkRegex (|[0-9]+)
 lookup _ [] _ = []
 lookup [] _ _ = []
 lookup match repl groups =
 case matchRegexAll bre repl of
 Nothing - repl
 Just (lead, _, trail, bgroups) -
 let newval = if (head bgroups) == \\
  then \\
  else let index = (read (head bgroups)) - 1
   in
   if index == -1
  then match
  else groups !! index
 in
 lead ++ newval ++ lookup match trail groups
 in
 case matchRegexAll regexp inp of
 Nothing - inp
 Just (lead, match, trail, groups) -
   lead ++ lookup match repl groups ++ (subRegex regexp trail repl)

You could just paste that code into a file that imports a different backend and
it should work since it uses just the type class API. You might also improve on
the above routine or specialize it.  The above handle \0 \1 \2 substitutions
(and \\ escaping) in the replacement string, including multi-digit references
such as \15 for very large regular expressions.  It operation only on [Char] and
is somewhat lazy.

  But which one to use? How hard to install? With the libs mentioned
  above, the PCRE-ness seems only to be for matching, not for
  substitutions.
 

I think if you paste the subRegex code above underneath an import
Text.Posix.PCRE declaration then you get what you are looking for.

To install:

The regex-* package hosting is via darcs and has been copied/moved to

http://darcs.haskell.org/packages/   (The stable regex-* versions)
http://darcs.haskell.org/packages/regex-unstable/  (The unstable regex-* 
versions)

so darcs get --partial http://darcs.haskell.org/packages/regex-pcre; might be
useful.

They have (hopefully working) cabal files to make compiling and installing easy.
 Note that regex-pcre and regex-tre need libpcre and libtre to be installed
separately.  regex-posix needs a posix library, but GHC already provides this
package with a working libary.

These 3 come with GHC:

regex-base defines the type classes and APIs and most RegexContext instances
regex-compat imitates the old Text.Regex API using regex-posix
regex-posix backend has awful performance.  Not for heavy use.

These 4 backends can be downloaded using darcs:

regex-pcre uses libpcre 

Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Yitzchak Gale

tphyahoo wrote:

There are various haskell regex libraries out there,


Jules Bean wrote:

But that's such a perler attitude. When all you have is a regex,
everything looks like a s///!


Not always, sometimes it is right to use regexes in Haskell
also.

If there are more than a few patterns to match in the same
string, or if the patterns are more than a few characters long,
then the simple approach will start becoming expensive.

You need to use a more sophisticated algorithm - building
up trees of potential matches, backtracking in some cases,
etc. Why re-invent the wheel? Just use the regex library,
where that is already done.

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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Jules Bean

Yitzchak Gale wrote:


You need to use a more sophisticated algorithm - building
up trees of potential matches, backtracking in some cases,
etc. Why re-invent the wheel? Just use the regex library,
where that is already done.



It's merely a question of selecting the right wheel. Some problems are 
so simple that regexes are overkill. Some problems are so complex that 
regexes are insufficient. Some problems generate extraordinarily ugly 
regexes, which are then hard-to-debug.


Some problems are perfectly suited to regexes.

Jules

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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Brandon S. Allbery KF8NH


On Jan 5, 2007, at 9:38 , Jules Bean wrote:


Yitzchak Gale wrote:

You need to use a more sophisticated algorithm - building
up trees of potential matches, backtracking in some cases,
etc. Why re-invent the wheel? Just use the regex library,
where that is already done.


It's merely a question of selecting the right wheel. Some problems  
are so simple that regexes are overkill. Some problems are so  
complex that regexes are insufficient. Some problems generate  
extraordinarily ugly regexes, which are then hard-to-debug.


I will note that the most common use for regexes in Perl is for  
parsing (which is why perl6 has generalized regexes into a parsing  
mechanism).


--
brandon s. allbery[linux,solaris,freebsd,perl] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH



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


Re: [Haskell-cafe] MVar style question

2007-01-05 Thread Chad Scherrer

Not that I've worked through yet. I really could be using IORef for
now, but I started using MVar because I might start using multiple
threads at some point, and I'd like to get comfortable with MVars for
that time.

On 1/4/07, Mike Gunter [EMAIL PROTECTED] wrote:


Do you need to maintain invariants that span the two?  Put
operationally, do you want different threads to be able to access a
and b concurrently?

-m

Chad Scherrer [EMAIL PROTECTED] writes:

 When using MVars, is there a reason to prefer using MVar (a,b) over
 (MVar a, MVar b), or vice versa? I'm not sure if this is really a
 question of style, or if there are practial implications I'm missing
 one way or another. Thanks!
 Chad Scherrer

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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Bill Wood
It would seem that for a regular expression facility to constitute a
parser it would have to be able to work on token streams. So my question
is, does either the the perl6 generalization or any of the Haskell regex
facilities support regular expressions over any free monoid other than
finite character sequences?

 -- Bill Wood



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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Chris Kuklewicz
Bill Wood wrote:
 It would seem that for a regular expression facility to constitute a
 parser it would have to be able to work on token streams. So my question
 is, does either the the perl6 generalization or any of the Haskell regex
 facilities support regular expressions over any free monoid other than
 finite character sequences?
 
  -- Bill Wood
 

Currently: The regular expressions themselves are finite, but some Haskell
regex-* backend packages can run searches on infinite [Char], since they are
lazy.  This is true of regex-parsec and regex-dfa.  In particular they take care
not to consume extra Char's from the input stream, though Parsec insists on
looking at the next character.

The regex-base type class API in Text.Regex.Base.RegexLike does not limit you to
any particular source of the regex or any particular type of thing to be
searched.  There is a limit that comes from using Int as the index of choice.
If you are searching something more that 2 billion units long then you would run
into API problems.  (One could just make a parallel BigRegex type class API and
make instances for it for the backends that can handle it.
).  Or I may expand it to take any (Num).  Hmmm.

Specifically, the RegerMaker is parameterized over source and regex and so
is completely generic.  This source is what specifies how to build the the
compiled regex opaque type.

Specifically, the Extract is parameterized over source (but limits the index
to Int).  This source is the type being searched.

Specifically, the RegexLike class is parameterized over regex and source,
where regex is the supposed to be the opaque compiled type from RegexMaker and
source is the type being searched.

Currently the RegexMaker source can be [Char] or ByteString and the
RegexLike/Extract source can be [Char] or ByteString.

Adding (Data.Sequence Char) would make sense, and perhaps (Data.Sequence Word8)
as ASCII.  If you write a very generic backend then you may be able to make more
generic instances of the API.  Note that the instances should be obvious because
your generic backend uses a unique opaque regex type.

Also not that the API is named Regex in several places but there is no need to
use anything like a Regex syntax.  In fact you could use something other than
RegexMaker to create the regex type used for specifying the
searching/matching.  I have not considered it until now, but maybe one could
create an instance of RegexLike based around Parsec's GenParser.

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


Re[2]: [Haskell-cafe] MVar style question

2007-01-05 Thread Bulat Ziganshin
Hello Chad,

Friday, January 5, 2007, 6:15:34 PM, you wrote:

 Thanks, you make some interesting points to consider. This leads me to
 wonder how these arguments might be extended to

 (1) IORef (a,b) vs. (IORef a, IORef b)

depends on whether you need to read/write both variables at the same or
different moments. also, IORef a may be optimized to IOURef a which
works faster

 (2) TVar (a,b) vs. (TVar a, TVar b)

i never worked with STM, but guess that TVar usage pattern is just the smae
as for MVar

btw, you can use type synonym to make switching from IORef to MVar easier:

type MyVar a = IORef a


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] GHC performance of 64-bit

2007-01-05 Thread Pedro Baltazar Vasconcelos


Hello all,

I noticed that GHC generates slower code on an Linux amd64 bit platform than 
the 32-bit version on a cheaper 32-bit machine.
CPUTime for running sieve of Erathostenes to generate 10,000 primes:
Athlon XP 2800 (32-bit): 7.98 secs
Athlon 64 3800 (64-bit): 10.29 secs
This is using GHC 6.6 on the 64-bit machine and 6.4.1 on the 32-bit one.

I googled around and could not find any information regarding degraded 
performance of ghc/haskell on 64-bit machines. Any ideas?

Regards,

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


[Haskell-cafe] Stupid newbie question

2007-01-05 Thread Brian Hurt


My apologies for wasting bandwidth on what I'm sure is a stupid newbie 
question.


Given:

-- Reimplementing the wheel here, I know

data Option a = Some a | Empty
deriving (Eq,Ord,Show,Read)

nth 0 (x:xs) = Some x
nth i (x:xs) = if i  0 then Empty else nth (i-1) xs
nth i [] = Empty

That:

nth 100 [1..1000]

returns the right answer, while:

nth 100 [1..]

blows stack.  Furthermore, given:

makelist i = i : (makelist (i-1))

Why is it that:
nth 100 (makelist 1)

blows stack?  What are the rules for being tail recursive in Haskell?  I'm 
an Ocaml programmer, so I'm familiar with this problem, I just don't see 
the solution.  Some help would be appreciated.


Thanks in advance,
Brian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Donald Bruce Stewart
bhurt:
 
 My apologies for wasting bandwidth on what I'm sure is a stupid newbie 
 question.
 
 Given:
 
 -- Reimplementing the wheel here, I know
 
 data Option a = Some a | Empty
   deriving (Eq,Ord,Show,Read)
 
 nth 0 (x:xs) = Some x
 nth i (x:xs) = if i  0 then Empty else nth (i-1) xs
 nth i [] = Empty
 
 That:
 
 nth 100 [1..1000]
 
 returns the right answer, while:
 
 nth 100 [1..]

Now I'm really intrigued, since the standard list-index function also
fails:

Prelude [1..] !! (10^6)
*** Exception: stack overflow

It's implemeeted roughly as:

nth xs n | n  0 = Nothing
nth [] _ = Nothing
nth (x:_)  0 = Just x
nth (_:xs) n = xs `nth` (n-1)

main = print $ [1..] `nth` (10^6)

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Jeremy Shaw
Hi,

In this case, the stack overflow you are seeing is due to laziness not
tail recursion.

Because you never demand the value of any element in the list, Haskell
never bothers to calculate it. So you have a list that looks like:

 [ i,  i - 1, (i - 1) - 1, ((i - 1) - 1 - 1), .. ]

So, by the time you get up to some big numbers, you have built up a
very large thunk. For some reason this is causing a stack overflow.

The easiest solution is to make things a little more strict. For
example, if you change:

nth i (x:xs) = if i  0 then Empty else nth (i-1) xs

to:

nth i (x:xs) = x `seq` (if i  0 then Empty else nth (i-1) xs)

This will force x enough that things do not overflow.

j.

ps. just a warning, seq is not entirely straightforward to use, so
while it works in this case, it may not always work for you. I think
there might be a wiki page somewhere that explains how to avoid space
leaks in greater detail, but I can't seem to find it.

Another solution that does not involve using seq would be to replace
the above line with these two lines:

nth i (0:xs) = if i  0 then Empty else nth (i-1) xs
nth i (_:xs) = if i  0 then Empty else nth (i-1) xs

In order to decide which case to use, the first element of the list
has to be fully evaluated -- so we don't get a huge thunk building
up. I don't think I have ever seen anyway take this approach in real
code -- but I thought it might help illuminate things a bit.

pps. I didn't explain why [1..100] works, but [1..] fails, because
I don't know :) It's a bit suprising to me...

j.




At Fri, 5 Jan 2007 20:17:33 -0500 (EST),
Brian Hurt wrote:
 
 
 My apologies for wasting bandwidth on what I'm sure is a stupid newbie 
 question.
 
 Given:
 
 -- Reimplementing the wheel here, I know
 
 data Option a = Some a | Empty
   deriving (Eq,Ord,Show,Read)
 
 nth 0 (x:xs) = Some x
 nth i (x:xs) = if i  0 then Empty else nth (i-1) xs
 nth i [] = Empty
 
 That:
 
 nth 100 [1..1000]
 
 returns the right answer, while:
 
 nth 100 [1..]
 
 blows stack.  Furthermore, given:
 
 makelist i = i : (makelist (i-1))
 
 Why is it that:
 nth 100 (makelist 1)
 
 blows stack?  What are the rules for being tail recursive in Haskell?  I'm 
 an Ocaml programmer, so I'm familiar with this problem, I just don't see 
 the solution.  Some help would be appreciated.
 
 Thanks in advance,
 Brian
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Jeremy Shaw
At Fri, 05 Jan 2007 17:58:14 -0800,
Jeremy Shaw wrote:

 Because you never demand the value of any element in the list, Haskell
 never bothers to calculate it. So you have a list that looks like:
 
  [ i,  i - 1, (i - 1) - 1, ((i - 1) - 1 - 1), .. ]

I should clarify that this is the list that will be built by:

 makelist i = i : (makelist (i-1))

[1..] will be building something like:

 [ 1, succ 1, succ (succ 1), succ (succ (succ 1)), ...]

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


Re: [Haskell-cafe] trivial function application question

2007-01-05 Thread Donald Bruce Stewart
tphyahoo:
 
 So the core question (speaking as a perler) is how do you write
 
   my $s= 'abcdefg';
   $s =~ s/a/z/g;
   $s =~ s/b/y/g;
   print $s\n;

Simple patterns like this you'd just use a 'map' of course:

main = print (clean abcdefg)

clean = map (by . az)
  where by c = if c == 'b' then 'y' else c
az c = if c == 'a' then 'z' else c

Running this:

$ runhaskell A.hs
zycdefg

Now, using regexes instead we can get by with just the regex-compat lib,
providing:

import Text.Regex

I usually flip the arguments to subRegex, since they're in the wrong
order for composition (anyone else noticed this?):

sub   re y s = subRegex re s y
regex= mkRegex


Now , using proper regexes, we can write:

main  = print (clean abcdefg)

clean = sub (regex b) y
  . sub (regex a) z

Running this:

$ runhaskell A.hs
zycdefg


Similar results will be achieved with the other regex-* packages:


http://haskell.org/haskellwiki/Libraries_and_tools/Compiler_tools#Regular_expressions

I think TRE might be preferred for high performance cases.

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Jason Creighton
On Fri, Jan 05, 2007 at 08:17:33PM -0500, Brian Hurt wrote:
 
 My apologies for wasting bandwidth on what I'm sure is a stupid newbie 
 question.
 
 Given:
 
 -- Reimplementing the wheel here, I know
 
 data Option a = Some a | Empty
   deriving (Eq,Ord,Show,Read)

My apologies if you knew this already, (I don't know whether your
Reimplementing the wheel comment refers to this type or the nth
function) but this is the Maybe data type in Prelude:

data Maybe a = Nothing | Just a

...which is the same as yours, except it's spelled differently, is an
instance of several handy classes (eg, Monad), and has a handful of
helper functions predefined: 
http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Maybe.html

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Brian Hurt



On Fri, 5 Jan 2007, Jeremy Shaw wrote:


Hi,

In this case, the stack overflow you are seeing is due to laziness not
tail recursion.


Aha.  I knew it was something stupid.



Because you never demand the value of any element in the list, Haskell
never bothers to calculate it. So you have a list that looks like:

[ i,  i - 1, (i - 1) - 1, ((i - 1) - 1 - 1), .. ]

So, by the time you get up to some big numbers, you have built up a
very large thunk. For some reason this is causing a stack overflow.



Actually, this makes sense to me.  Recursively forcing lazy thunks is not 
tail recursive, it needs to allocate stack frames.  So if a million-deep 
recursive thunk, forcing it is a problem.



The easiest solution is to make things a little more strict. For
example, if you change:

nth i (x:xs) = if i  0 then Empty else nth (i-1) xs

to:

nth i (x:xs) = x `seq` (if i  0 then Empty else nth (i-1) xs)

This will force x enough that things do not overflow.

j.

ps. just a warning, seq is not entirely straightforward to use, so
while it works in this case, it may not always work for you. I think
there might be a wiki page somewhere that explains how to avoid space
leaks in greater detail, but I can't seem to find it.

Another solution that does not involve using seq would be to replace
the above line with these two lines:

nth i (0:xs) = if i  0 then Empty else nth (i-1) xs
This looks to be a typo, not sure if it's mine or yours.  The definition I 
was playing with was (or should be):


nth i (x:xs) = if i  0 then Empty else nth (i-1) xs

Brian

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Brian Hurt



On Fri, 5 Jan 2007, Jason Creighton wrote:


On Fri, Jan 05, 2007 at 08:17:33PM -0500, Brian Hurt wrote:


My apologies for wasting bandwidth on what I'm sure is a stupid newbie
question.

Given:

-- Reimplementing the wheel here, I know

data Option a = Some a | Empty
deriving (Eq,Ord,Show,Read)


My apologies if you knew this already, (I don't know whether your
Reimplementing the wheel comment refers to this type or the nth
function) but this is the Maybe data type in Prelude:

data Maybe a = Nothing | Just a


Both, actually.  I did the Option a definition to get some experience with 
defining symbolic data types, and probably should have removed it in my 
example.




...which is the same as yours, except it's spelled differently, is an
instance of several handy classes (eg, Monad), and has a handful of
helper functions predefined: 
http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Maybe.html


Thanks for the link.

Brian

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Brian Hurt



On Fri, 5 Jan 2007, Jeremy Shaw wrote:


The easiest solution is to make things a little more strict. For
example, if you change:

nth i (x:xs) = if i  0 then Empty else nth (i-1) xs


Even better, if I define:

nth 0 (x:_) = Just x
nth i (_:xs) = if i  0 then Nothing else nth (i-1) xs
nth i [] = Nothing

makelist i = i `seq` i : (makelist (i+1))

nth 1000 (makelist 1)

This works like a charm.  Thanks.

Brian

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Mike Gunter


 pps. I didn't explain why [1..100] works, but [1..] fails, because
 I don't know :) It's a bit suprising to me...

With [1..100], the generated values have to be tested against
100 as you go.  So, they get evaluated.  In the [1..] case,
they don't.

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Jeremy Shaw
At Fri, 05 Jan 2007 20:59:16 -0800,
Mike Gunter wrote:
 
 
 
  pps. I didn't explain why [1..100] works, but [1..] fails, because
  I don't know :) It's a bit suprising to me...
 
 With [1..100], the generated values have to be tested against
 100 as you go.  So, they get evaluated.  In the [1..] case,
 they don't.

Ah, that makes a lot of sense. Thanks!

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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Bernie Pope


On 06/01/2007, at 12:58 PM, Jeremy Shaw wrote:


Because you never demand the value of any element in the list, Haskell
never bothers to calculate it. So you have a list that looks like:

 [ i,  i - 1, (i - 1) - 1, ((i - 1) - 1 - 1), .. ]

So, by the time you get up to some big numbers, you have built up a
very large thunk. For some reason this is causing a stack overflow.


Right. And to clarify, the reason is that the thunk is one big chain  
of applications of

(-). Imagine what will happen when the topmost application is evaluated.
Because (-) is strict in its arguments they must be evaluated before  
the minus can
proceed. So the left and right arguments are evaluated. The left  
argument is itself
an application of (-)  and so on. The whole left branch eventually  
gets pushed onto the stack.

Because the left branch is so long, the stack eventually overflows.

This is one of those examples where optimistic evaluation would be a  
win.


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


Re: [Haskell-cafe] Stupid newbie question

2007-01-05 Thread Marc A. Ziegert
Am Samstag, 6. Januar 2007 05:12 schrieb Brian Hurt:
 Even better, if I define:
 
 nth 0 (x:_) = Just x
 nth i (_:xs) = if i  0 then Nothing else nth (i-1) xs
 nth i [] = Nothing
 
 makelist i = i `seq` i : (makelist (i+1))
 
 nth 1000 (makelist 1)
 

Hi Brian.
i just like to mention another tricky solution:
you can apply seq in such a way to the list, so that each element will be 
evaluated before advancing deeper into the list.


ghci -fglasgow-exts -fbang-patterns

Prelude :t foldr
foldr :: forall a b. (a - b - b) - b - [a] - b

Prelude let strict = foldr (\x xs -x `seq` (x:xs)) []
Prelude let strict = foldr (\(!x) xs - (x:xs)) [] --  using bang patterns 
instead, this is easier to read
Prelude let strict = foldr ((:) $!) [] --  or complete 
pointfree
Prelude let lazy   = foldr ((:) $) []
Prelude :t strict
strict :: forall a. [a] - [a]

Prelude lazy [1..] !! 100
*** Exception: stack overflow
Prelude strict [1..] !! 100
101



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