Re: [Haskell-cafe] Re: Bathroom reading

2007-08-17 Thread Albert Y. C. Lai

Dan Weston wrote:

I hate to be a party pooper, but isn't this just:

 > f = foldr (\a z -> (a:snd z,fst z)) ([],[])

This takes less time to grok and takes no longer to run.


For each type with exported constructors, one can always write 
deconstructors for it, if not already found in libraries. One may then 
argue that ~ is never necessary. Given


f ( ~(Left (z0,_)) : Right ~(Just z1) : xs ) = (z0, z1, xs)

you can always hand-compile to

f (x0 : Right y1 : xs) = (fst (getLeft x0), fromJust y1, xs)

But ~ is desirable:

0. Which version is easier to understand?

That is a bit subjective, but I think it comes down to this. (As do all 
debates over whether concise notation is readable, really.) To a kid who 
has not learned the word "arctan", I have to say, "draw this 
right-angled triangle, with this side being length 3, that side being 
length 4, now measure this angle, that is what I mean by arctan(3/4)" - 
you know, all the details, step by step, hand in hand. To a learned 
adult, I can just say, "arctan". In fact, if I spelt out the details to 
the adult, step by step, hand in hand, he/she would think I'm 
condescending or counterproductive.


Specifically in the case of ~, it makes transparent the structure of the 
data to be expected: By just reading one spot, you see it wants a list 
of two or more items, the first item is a Left, in which there is a 
tuple, the second item is a Right, in which there is a Just.


That same information is torned apart without ~: part of the information 
is on the left, and the rest is hidden on the right to be recovered from 
the deconstructor calls and re-constructing the picture in your head. 
This is because it is more low-level. The "what" is encoded beneath the 
"how". You follow the code execution and then you reverse-engineer its 
purpose. It is quite attractive when you have no notation to denote the 
purpose. It is a poor choice when you have a notation to denote the 
purpose: "what" data parts are wanted, and "when" they are wanted, 
without reading a single function call, the "how".


1. Which version is easier to change strictness?

Strictness and non-strictness are tricky to get right for performance or 
even mere feasibility. An important programming activity is 
investigating various levels of strictness. It is imperative to be able 
to change strictness efficiently.


~ is already a non-strictness annotation. Anyone who already understands 
the ! strictness annotation understands this one too. By just toggling 
~'s you toggle non-strictness. It's that easy to change.


Here is the function again. I'm going to change its strictness.

f ( ~(Left (z0,_)) : Right ~(Just z1) : xs ) = (z0, z1, xs)

I now want the second cons to be later, the Left to be earlier (at the 
same time as the first cons), the tuple to be later, the Right to be 
later (even later than the second cons), and the Just to be earlier (at 
the same time as the Right). I can do that by just toggling ~'s:


f ( Left ~(z0,_) : ~(~(Right (Just z1)) : xs) ) = (z0, z1, xs)

Without ~, much more change is necessary. Here is the non-~ code before 
change again:


f (x0 : Right y1 : xs) = (fst (getLeft x0), fromJust y1, xs)

The change is:

f (Left y0 : xs) = (fst y0, fromJust (getRight (head xs)), tail xs)

Both sides have to be changed. On the left, the data structure has to be 
changed. On the right, the function call structure has to be changed. 
You have to remove a constructor on the left and add a deconstructor on 
the right, or add a constructor on the left and remove a deconstructor 
on the right. This is a dream come true for IDE marketeers. This code 
manipulation is too annoying to be done by hand on a daily basis, yet 
mechanical enough to be done by software easily. A marketeer can sell an 
IDE plugin for this and garner much money and gratitude from 
unsuspecting programmers, capitalizing on the fact that some languages 
do not provide an annotation to trivialize this whole business, and in 
those that do, some programmers refuse to use it.


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


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Tim Chevalier
On 8/17/07, Kim-Ee Yeoh <[EMAIL PROTECTED]> wrote:
> Incidentally, GHC's type checker is Turing complete. You
> already have as much static evaluation as is practically possible.
> You already knew that.
>

I don't see how the first statement implies the second.

Cheers,
Tim

-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
"It's never too early to start drilling holes in your car."  -- Tom Magliozzi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Lennart Augustsson
On 8/17/07, Kim-Ee Yeoh <[EMAIL PROTECTED]> wrote:
>
>
>
> Lennart Augustsson wrote:
> >
> > And as a previous poster showed, ghc does concatenate strings.
> >
>
> And Haskell (as in the current language definition) does not.
> I was talking about Haskell.


Haskell says nothing about compile time or run time in the language
definition.  Nor does it say exactly when things are evaluated.  Even the
tag line for Haskell says "non-strict" rather than lazy.
So Haskell semantics allows many evaluation strategies, and evaluating
terminating constant expression at compile time is certainly one of them.
You don't have to, but it's permissible.

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


Re: [Haskell-cafe] trouble compiling "import GHC.Prim(MutableByteArray#, ....." (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-17 Thread Stefan O'Rear
On Fri, Aug 17, 2007 at 08:13:55PM -0400, Thomas Hartman wrote:
> Thanks Stefan. I got regex tdfa to compile on 6.7. FWIW, here's a patch, 
> generated with darcs whatsnew against a fresh unzip of regex tdfa 0.92
>
> I didn't patch against the darcs head because this uses a "language" 
> progma in {-# options #-} in some file*, which ghc 6.7 didn't know what to 
> do with, nor I.
>
> *: Text/Regex/TDFA/RunMutState.hs: {-# LANGUAGE CPP #-} (in darcs head, 
> which as I said, I did not patch against, rather I patched against 0.92 
> downloaded and unzipped.)

That's a bug, in either GHC 6.7.x (please specify the date if you can,
6.7 is a pretty wide range!) or regex-tdfa.

Does {-# OPTIONS_GHC -cpp #-} (theoretically equivalent) work?

What's the error message?

> If there is a better way than this to send patches please advise, as I 
> don't do this terribly often. (Actually I have no idea how to apply the 
> below patch... is there a way?)

$ mkdir ~/.darcs
$ echo 'Thomas Hartman <[EMAIL PROTECTED]>' > ~/.darcs/author
$ darcs record -a

$ darcs send

> [patch]

> {
> hunk ./Data/IntMap/CharMap.hs 1
> +{-# OPTIONS -XGeneralizedNewtypeDeriving #-}

Ick.  {-# OPTIONS is very strongly deprecated, since it doesn't specify
a compiler but must use a compiler-specific syntax.  Much better to use
LANGUAGE:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

> +Build-Depends:  regex-base >= 0.80, base >= 2.0, parsec, mtl, 
> containers, array, bytestring

That won't work; you must indent continuation lines.

Stefan


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


Re: [Haskell-cafe] trouble compiling "import GHC.Prim(MutableByteArray#, ....." (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-17 Thread Thomas Hartman
Thanks Stefan. I got regex tdfa to compile on 6.7. FWIW, here's a patch, 
generated with darcs whatsnew against a fresh unzip of regex tdfa 0.92

I didn't patch against the darcs head because this uses a "language" 
progma in {-# options #-} in some file*, which ghc 6.7 didn't know what to 
do with, nor I.

*: Text/Regex/TDFA/RunMutState.hs: {-# LANGUAGE CPP #-} (in darcs head, 
which as I said, I did not patch against, rather I patched against 0.92 
downloaded and unzipped.)

If there is a better way than this to send patches please advise, as I 
don't do this terribly often. (Actually I have no idea how to apply the 
below patch... is there a way?)

{
hunk ./Data/IntMap/CharMap.hs 1
+{-# OPTIONS -XGeneralizedNewtypeDeriving #-}
hunk ./Data/IntMap/EnumMap.hs 1
+{-# OPTIONS -XGeneralizedNewtypeDeriving #-}
hunk ./Data/IntSet/EnumSet.hs 1
+{-# OPTIONS -XGeneralizedNewtypeDeriving #-}
hunk ./Text/Regex/TDFA/ByteString/Lazy.hs 1
-{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# OPTIONS_GHC -fno-warn-orphans -fglasgow-exts #-}
hunk ./Text/Regex/TDFA/Common.hs 1
-{-# OPTIONS -funbox-strict-fields #-}
+{-# OPTIONS -funbox-strict-fields -XGeneralizedNewtypeDeriving #-}
hunk ./Text/Regex/TDFA/CorePattern.hs 1
+{-# OPTIONS -fglasgow-exts #-}
hunk ./Text/Regex/TDFA/CorePattern.hs 38
+import Data.Monoid
+import Control.Monad
hunk ./Text/Regex/TDFA/RunMutState.hs 1
+{-# OPTIONS -fglasgow-exts #-}
hunk ./Text/Regex/TDFA/String.hs 1
-{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# OPTIONS_GHC -fno-warn-orphans -fglasgow-exts #-}
hunk ./Text/Regex/TDFA/TDFA.hs 1
+{-# OPTIONS -fglasgow-exts #-}
hunk ./Text/Regex/TDFA/TDFA.hs 12
-import Control.Monad.RWS
+import Control.Monad (mplus)
+--import Control.Monad.RWS
hunk ./Text/Regex/TDFA/TDFA.hs 33
+import Data.Monoid
+
hunk ./Text/Regex/TDFA/TNFA.hs 1
-{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# OPTIONS_GHC -fno-warn-orphans -fglasgow-exts #-}
hunk ./Text/Regex/TDFA/Wrap.hs 1
-{-# OPTIONS -fno-warn-orphans #-}
+{-# OPTIONS -fno-warn-orphans -fglasgow-exts #-}
hunk ./Text/Regex/TDFA.hs 42
-  ,module Text.Regex.TDFA.String
-  ,module Text.Regex.TDFA.ByteString
-  ,module Text.Regex.TDFA.ByteString.Lazy
-  ,module Text.Regex.TDFA.Sequence
+  --,module Text.Regex.TDFA.String
+  --,module Text.Regex.TDFA.ByteString
+  --,module Text.Regex.TDFA.ByteString.Lazy
+  --,module Text.Regex.TDFA.Sequence
hunk ./regex-tdfa.cabal 16
-Build-Depends:  regex-base >= 0.80, base >= 2.0, parsec, mtl
+Build-Depends:  regex-base >= 0.80, base >= 2.0, parsec, mtl, 
containers, array, bytestring
}





"Stefan O'Rear" <[EMAIL PROTECTED]> 
08/17/2007 04:47 PM

To
Thomas Hartman/ext/[EMAIL PROTECTED]
cc
haskell-cafe 
Subject
Re: [Haskell-cafe] trouble compiling "import GHC.Prim(MutableByteArray#, 
."  (building regex-tdfa from   darcs) -- what's that # sign 
doing?






On Fri, Aug 17, 2007 at 04:27:29PM -0400, Thomas Hartman wrote:
> trying to compile regex-tdfa, I ran into another issue. (earlier I had a 

> cabal problem but that's resolved.)
> 
> there's a line that won't compile, neither for ghc 6.6.1 nor 6.7 
> 
> import 
> 
GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
> 
> so the fresh darcs regex tdfa package won't build.
> 
> This line (line 16 below) causes this error for 
> 
>   ghc -e '' RunMutState.hs
> 
> for both ghc 6.1 and 6.7 

There are at least two things going on here.

1. GHC-specific unboxed identifiers have a # in the name.   I think this
   is a relic from back when the only reasonable way to namespace was to
   modify your compiler to add extra identifier characters, and use them
   in all non-portable identifiers.  In any case, you have to enable the
   -fglasgow-exts option (or -XMagicHash in recent 6.7) to allow imports
   of such identifiers.

2. Explicitly importing GHC.Prim has been discouraged for as long as I
   can remember, and GHC HQ has finally made good on the promise to make
   it impossible.  Code which imports it has a bug already, which can be
   fixed by switching to GHC.Exts.  (Why?  GHC.Prim is wired into the
   compiler, while GHC.Exts is a normal Haskell module, so by using
   GHC.Exts you are insulated from questions of what is primitive and
   what is derived but still unportable.  Yes, this does change.)

Stefan
[attachment "signature.asc" deleted by Thomas Hartman/ext/dbcom] 


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Remember the future

2007-08-17 Thread Paul Johnson

[EMAIL PROTECTED] wrote:

Andrew Coppin writes:
I've seen comments in various places that monads allow you to "borrow 
things from the future".

That sounds completely absurd to me... can anybody explain?


Actually, "borrowing from the future" - in an interpretation which is 
close
to my own interests - doesn't need monads, but *laziness*. 


While this is true, the "mdo" and associated MonadFix class do implement 
it in a monadic framework where you can write things like


  mdo
 x <- f y
 y <- g x

If you interpret do-notation as equivalent to imperative programming 
then this does indeed look like time travel.  Under the covers its more 
equivalent to


  let
 x = f y
 y = g x

which is also known as "tying the knot" or the "credit card transform" 
(both keywords worth looking up).


However I can't say I really have my head around it properly.

Paul.

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


Re: [Haskell-cafe] Remember the future

2007-08-17 Thread jerzy . karczmarczuk
Andrew Coppin writes: 

I've seen comments in various places that monads allow you to "borrow 
things from the future". 


That sounds completely absurd to me... can anybody explain?


Actually, "borrowing from the future" - in an interpretation which is close
to my own interests - doesn't need monads, but *laziness*. If you find this
absurd, I propose that you have a look on something a bit light, my paper
on a quite crazy way to compute PI with a high precision. The algorithm (not
mine, but of Bailey, Borwein and Plouffe) is a masterpiece of numerical
math, but its implementation relies on a mad borrowing from the future. 

http://users.info.unicaen.fr/~karczma/arpap/lazypi.pdf 


If you don't choke, try another one, the reverse automatic differentiation
algorithm, implemented using a variant of the Wadler's "counter-temporal"
state monad. 

http://users.info.unicaen.fr/~karczma/arpap/revdf1.pdf 


It is quite serious, although inefficient, and has some affinities to the
lazy processing of inherited attributes during parsing. 


More recently, Barak Pearlmutter and Jeff Siskind worked on similar issues,
but I am not sure whether they submitted something ready for the audience.
Please check it out. 

Jerzy Karczmarczuk 


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


Re: [Haskell-cafe] monte carlo trouble

2007-08-17 Thread Paul Johnson
I finally decided to actually solve the problem, and  I'm sorry to say I 
was on the wrong track.  ListT won't do it on its own: you actually need 
a custom monad that does the random pick in the bind operation.  
Attached are a module to solve the problem and a Main module that tests 
it.  I hope this helps.


Paul.
-- | Test the MonteCarlo Monad

module Main where

import System.Random
import MonteCarlo


f, g :: Int -> MonteCarlo Int
f x = returnList $ map (*3) [x .. x+( x `mod` 5)-1]

g x = returnList $ map (*2) [x .. x+( x `mod` 7)-1]


-- The actual Monte-Carlo computation
experiment :: [Int] -> MonteCarlo (Int, Int, Int)
experiment xs = do
   x  <- returnList xs
   f1 <- f x
   g1 <- g x
   return (x, f1, g1)


-- Infinite list of generators
generators :: StdGen -> [StdGen]
generators g = g1 : generators g2
   where (g1, g2) = split g


main :: IO ()
main = do
   g <- getStdGen
   print $ take 10 $ map (runMonteCarlo $ experiment [1..100]) $ generators g


-- | A monad of random non-determinism.  Each action in the computation
-- generates zero or more results.  Zero is failure, but if more than one
-- result is returned then one is selected at random.

module MonteCarlo (
   MonteCarlo,
   runMonteCarlo,
   returnList
) where

import Control.Monad
import System.Random

newtype MonteCarlo a = MonteCarlo {runMC :: StdGen -> (StdGen, [a])}


-- | Run a Monte-Carlo simulation to generate a zero or one results.
runMonteCarlo :: MonteCarlo a -> StdGen -> Maybe a
runMonteCarlo (MonteCarlo m) g1 =
   let
  (g2, xs) = m g1
  (_,  x)  = pickOne xs g2
   in case xs of
  []   -> Nothing
  [x1] -> Just x1
  _-> Just x


-- Internal function to pick a random element from a list
pickOne :: [a] -> StdGen -> (StdGen, a)
pickOne xs g1 = let (n, g2) = randomR (0, length xs - 1) g1 in (g2, xs !! n)


instance Monad MonteCarlo where
   MonteCarlo m >>= f  = MonteCarlo $ \g1 -> 
  let -- If I was clever I'd find a way to merge this with runMonteCarlo.
 (g2, xs)  = m g1
 (g3, x)   = pickOne xs g2
 f'= case xs of
[]   -> mzero
[x1] -> f x1
_-> f x
  in runMC f' g3

   return x = MonteCarlo $ \g -> (g, [x])
   

instance MonadPlus MonteCarlo where
   mzero = MonteCarlo $ \g -> (g, [])
   mplus (MonteCarlo m1) (MonteCarlo m2) = MonteCarlo $ \g ->
  let
(g1, xs1) = m1 g
(g2, xs2) = m2 g1
  in (g2, xs1 ++ xs2)


-- | Convert a list of items into a Monte-Carlo action.
returnList :: [a] -> MonteCarlo a
returnList xs = MonteCarlo $ \g -> (g, xs)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] defining last using foldr

2007-08-17 Thread Chaddaï Fouché
2007/8/18, Chaddaï Fouché <[EMAIL PROTECTED]>:
> For a really good article to see how foldr is in fact very powerful
> and how you can make it do some funny tricks, see the Monad.Reader 6th
> issue :
> http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf
>

I just saw this was already linked in this thread, sorry for the noise...

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


Re: [Haskell-cafe] defining last using foldr

2007-08-17 Thread Chaddaï Fouché
For a really good article to see how foldr is in fact very powerful
and how you can make it do some funny tricks, see the Monad.Reader 6th
issue :
http://www.haskell.org/sitewiki/images/1/14/TMR-Issue6.pdf

I'll point out that you can write a lazy dropWhile with foldr in the
style of the first example of the article just by using a
non-refutable pattern in the combine function :

dWLazy p = snd . foldr (\a ~(x, y) -> if p a then (a : x, y) else (a :
x, a : x)) ([], [])

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


[Haskell-cafe] What to do about an absent package maintainer?

2007-08-17 Thread Adam Langley
The HsOpenSSL package[1] is good work, but the author doesn't respond
to email(*). I've a bunch of darcs patches to add tests, DSA support
and fast Integer <-> BIGNUM functions. Can I use my Hackage account to
upload version 0.2 if someone else uploaded 0.1? It is reasonable?

I'm guessing that this issue will start to occur more often now that
we have Hackage. It's probably good to have some policy.


Cheers,

(*) It's been > 1 month, with emails from several different addresses.

[1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HsOpenSSL-0.1

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread Bryan O'Sullivan

Joe Buehler wrote:


What is the point in building this huge thunk if it can't be evaluated
without a stack overflow?


It's not that there's a point to it, it's just the behaviour of foldl. 
  Hence you shouldn't be using foldl.


GHC's strictness analyser can sometimes save you from yourself if you're 
compiling with -O, but it's better to just avoid foldl and use foldr or 
Data.List.foldl' instead.


http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Remember the future

2007-08-17 Thread Dan Piponi
On 8/17/07, Dan Piponi <[EMAIL PROTECTED]> wrote:
> On 8/17/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> > That sounds completely absurd to me... can anybody explain?
> Except...you can switch on ghc's special time travel features...

On reflection I decided my example isn't very convincing. For one
thing, I've argued in another thread that monads aren't really about
sequencing actions. But I concede that there is an exception: the IO
monad. Because the IO monad has observable side effects you can
actually see whether or not an action has taken place at a particular
time, so it really does have to sequence actions. So now consider the
following code:

> import IO
> import Control.Monad.Fix

> test = mdo
> z <- return $ x+y
> print "Hello"
> x <- readLn
> y <- readLn
> return z

Evaluate test and you'll be prompted to enter a pair of numbers.
You'll then be rewarded with their sum. But the "Hello" message is
printed before the prompt for input so we know that's being executed
first. And we can see clearly that the summation is performed before
the "Hello" message. So clearly this program is computing its result
before receiving the input.

At this point your natural reaction should be to replace 'print
"Hello"' with 'print z'...
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Remember the future

2007-08-17 Thread Dan Piponi
On 8/17/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
> I've seen comments in various places that monads allow you to "borrow
> things from the future".
>
> That sounds completely absurd to me... can anybody explain?

Suppose you buy into the notion that monads sequence actions. Then
consider the following code:

> import Control.Monad.State

> test = do
> put $ x+1
> x <- return 1
> return undefined

> go = execState test undefined

execState runs a sequence of actions in the state monad, ignoring the
returned value and simply giving you back the resulting state. So work
through what this code does:

It sets the value of the state to be 1+x. It then sets x to be 1. And
then it returns undefined. We don't care about the return value, we
just care about the state. And clearly the state is 2. But if you
believe all that action sequencing stuff, we set the state using x
before we actually set the value of x. So we're reading from the
future.

But you can breathe a sigh of relief because the above code doesn't
compile and the laws of physics remain unharmed.

Except...you can switch on ghc's special time travel features using
the -fglasgow-exts flag. Use the time-travel compatible mdo instead of
do and you'll find that this compiles and runs fine:

> import Control.Monad.State
> import Control.Monad.Fix

> test = mdo
> put $ x+1
> x <- return 1
> return undefined

> go = execState test undefined
--
Dan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Remember the future

2007-08-17 Thread Andrew Coppin

Gwern Branwen wrote:

On  0, Andrew Coppin <[EMAIL PROTECTED]> scribbled:
  

I've seen comments in various places that monads allow you to "borrow
things from the future".

That sounds completely absurd to me... can anybody explain?



Take a look at issue 6 of The Monad Reader; search for time travel. 

  


Mmm... yes... I've read this before. It didn't make any sense then 
either. (The example is too big and complicated. It obscures the thing 
it's trying to illustrate...)


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


[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread Joe Buehler
Matthew Brecknell wrote:

> The key point of the example is that foldl itself doesn't need any of
> the intermediate values of the accumulator, so these just build up into
> a deeply-nested unevaluated thunk. When print finally demands an
> integer, the run-time pushes a stack frame for each level of parentheses
> it enters as it tries to evaluate the thunk. Too many parentheses leads
> to a stack overflow. Of course, the solution to the example is to use

What is the point in building this huge thunk if it can't be evaluated
without a stack overflow?  Could the runtime do partial evaluation
to keep the thunk size down or would that cause semantic breakage?

Joe Buehler

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


Re: [Haskell-cafe] trouble compiling "import GHC.Prim(MutableByteArray#, ....." (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-17 Thread Stefan O'Rear
On Fri, Aug 17, 2007 at 04:27:29PM -0400, Thomas Hartman wrote:
> trying to compile regex-tdfa, I ran into another issue. (earlier I had a 
> cabal problem but that's resolved.)
> 
> there's a line that won't compile, neither for ghc 6.6.1 nor 6.7 
> 
> import 
> GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
> 
> so the fresh darcs regex tdfa package won't build.
> 
> This line (line 16 below) causes this error for 
> 
>   ghc -e '' RunMutState.hs
> 
> for both ghc 6.1 and 6.7 

There are at least two things going on here.

1. GHC-specific unboxed identifiers have a # in the name.   I think this
   is a relic from back when the only reasonable way to namespace was to
   modify your compiler to add extra identifier characters, and use them
   in all non-portable identifiers.  In any case, you have to enable the
   -fglasgow-exts option (or -XMagicHash in recent 6.7) to allow imports
   of such identifiers.

2. Explicitly importing GHC.Prim has been discouraged for as long as I
   can remember, and GHC HQ has finally made good on the promise to make
   it impossible.  Code which imports it has a bug already, which can be
   fixed by switching to GHC.Exts.  (Why?  GHC.Prim is wired into the
   compiler, while GHC.Exts is a normal Haskell module, so by using
   GHC.Exts you are insulated from questions of what is primitive and
   what is derived but still unportable.  Yes, this does change.)

Stefan


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


Re: [Haskell-cafe] GHC linking problems

2007-08-17 Thread SevenThunders

Did I find a bug cabal?
I have attempted to fix the problem 

Main.c:(.text+0x22): undefined reference to `__stginit_ZCMain'

by compiling my Haskell library using the flag -no-hs-main.  One would think
that this would make sense if the library is to be used by an external C
program.  However I am using cabal to build the haskell library and I
immediately run into a problem.  My netsim.cabal file looks like

Name:   Netsim
Version:1.1
License:AllRightsReserved
Exposed-modules:
Matrix, Parsefile, PowCDF
Build-Depends:  
base, regex-compat>=0.71, parsec>=2.0
Extensions: ForeignFunctionInterface
Includes:   matrixstack.h
Install-includes: matrixstack.h, TunePerf.h 
Include-dirs:   ../matrixstack, /usr/lib/ghc-6.6.1/include, .
Extra-libraries: netsimc, matrixstack, lapack, ptcblas, atlas
Extra-lib-dirs: /usr/local/atlas/lib, ., ./phymake,../matrixstack
Ghc-options: -fglasgow-exts -O2 -no-hs-main

My setup.hs file looks like:
import Distribution.Simple
main = defaultMainWithHooks defaultUserHooks

When I build this using
runhaskell Setup.hs build 
all the source files compile just fine, but then a screwy thing happens. 
Cabal attempts to build an executable called a.out. Moreover a.out has no
main of course and it does not attempt to link to any of the libraries in
the Extra-libraries field.
This kills the cabal build.  So trying to link a.out (which it shouldnt be
doing) gives me the errors,
Preprocessing library Netsim-1.1...
Building Netsim-1.1...
Linking a.out ...
dist/build/Matrix.o: In function `Netsimzm1zi1_Matrix_zdwccall_info':
ghc6835_0.hc:(.text+0x1ea9): undefined reference to `PmatC'
dist/build/Matrix.o: In function `Netsimzm1zi1_Matrix_zdwccall1_info':
ghc6835_0.hc:(.text+0x1f79): undefined reference to `Pmat'
dist/build/Matrix.o: In function `Netsimzm1zi1_Matrix_zdwccall2_info':
...
/usr/lib/ghc-6.6.1/libHSrts.a(Main.o): In function `main':
Main.c:(.text+0x22): undefined reference to `__stginit_ZCMain'
Main.c:(.text+0x43): undefined reference to `ZCMain_main_closure'

If I eliminate the -no-hs-main flag in Ghc-options  no attempt is made to
creat a.out, which is as it should be and the library builds without
complaint.  This seems like a bug in cabal.
-- 
View this message in context: 
http://www.nabble.com/GHC-linking-problems-tf4270650.html#a12206722
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] trouble compiling "import GHC.Prim(MutableByteArray#, ....." (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-17 Thread Thomas Hartman
trying to compile regex-tdfa, I ran into another issue. (earlier I had a 
cabal problem but that's resolved.)

there's a line that won't compile, neither for ghc 6.6.1 nor 6.7 

import 
GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)

so the fresh darcs regex tdfa package won't build.

This line (line 16 below) causes this error for 

  ghc -e '' RunMutState.hs

for both ghc 6.1 and 6.7 

Much obliged for any help,

Thomas.

*

[EMAIL PROTECTED]:~/installs/regex_darcs/regex-tdfa>runghc Setup.hs build
Preprocessing library regex-tdfa-0.93...
Building regex-tdfa-0.93...

Text/Regex/TDFA/RunMutState.hs:16:32: parse error on input `#'
[EMAIL PROTECTED]:~/installs/regex_darcs/regex-tdfa>head -n20 
Text/Regex/TDFA/RunMutState.hs | cat -n 
 1  {-# LANGUAGE CPP #-}
 2  module 
Text.Regex.TDFA.RunMutState(TagEngine(..),newTagEngine,newTagEngine2
 3,newScratch,tagsToGroupsST
 4 ,toInstructions,compareWith,resetScratch
 5,SScratch(..),MScratch,WScratch) 
where
 6 
 7  import Control.Monad(forM_,liftM,liftM2,liftM3,foldM)
 8  --import Control.Monad.ST.Strict as S (ST)
 9  --import qualified Control.Monad.ST.Lazy as L (ST)
10  import Control.Monad.State(MonadState(..),execState)
11 
12  import Data.Array.Base(unsafeRead,unsafeWrite,STUArray(..))
13  #ifdef __GLASGOW_HASKELL__
14  import GHC.Arr(STArray(..))
15  import GHC.ST(ST(..))
*** 16  import 
GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
17  #else
18  import Control.Monad(when)
19  import Control.Monad.ST(ST)
20  import Data.Array.ST(STArray)
[EMAIL PROTECTED]:~/installs/regex_darcs/regex-tdfa>



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trouble building regex-base 0.91 on ghc 6.7

2007-08-17 Thread Thomas Hartman
thanks stefan, I did remember that discussion (actually also an answer to 
a question I asked.)

I got from that that previous help that I had to edit the cabal file.

The problem here, as you say, is that I had not re-run runghc Setup.hs 
configure.

thanks,

thomas.



"Stefan O'Rear" <[EMAIL PROTECTED]> 
08/17/2007 03:00 PM

To
Thomas Hartman/ext/[EMAIL PROTECTED]
cc
haskell-cafe 
Subject
Re: [Haskell-cafe] trouble building regex-base 0.91 on ghc 6.7






On Fri, Aug 17, 2007 at 02:40:33PM -0400, Thomas Hartman wrote:
> I'm trying to build the latest regex base, which is required for the 
other 
> regex packages under ghc 6.7
> 
> It complains that it can't find Data.Sequence, because it's in a hidden 
> module containers. I added containers to the cabal depends as can be 
seen 
> in the grep below.
> 
> And containers isn't hidden when I do ghc-pkg list.
> 
> What gives?
> 
> Still getting used to cabal...

Did you re-run configure after changing the cabal file?

Also, what ghc-pkg says has absolutely nothing to do with this; the
options Cabal passes completely override the ghc-pkg exposure flags.I
can hardly fault you for not knowing the answer to a Cabal FAQ, since
Cabal doesn't actually have a FAQ list yet.

You are running into the same problem as
http://www.haskell.org/pipermail/haskell-cafe/2007-August/030276.html,
and most of my explanation there applies here.

Stefan
[attachment "signature.asc" deleted by Thomas Hartman/ext/dbcom] 


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Remember the future

2007-08-17 Thread Andrew Coppin
I've seen comments in various places that monads allow you to "borrow 
things from the future".


That sounds completely absurd to me... can anybody explain?

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


Re: [Haskell-cafe] trouble building regex-base 0.91 on ghc 6.7

2007-08-17 Thread Stefan O'Rear
On Fri, Aug 17, 2007 at 02:40:33PM -0400, Thomas Hartman wrote:
> I'm trying to build the latest regex base, which is required for the other 
> regex packages under ghc 6.7
> 
> It complains that it can't find Data.Sequence, because it's in a hidden 
> module containers. I added containers to the cabal depends as can be seen 
> in the grep below.
> 
> And containers isn't hidden when I do ghc-pkg list.
> 
> What gives?
> 
> Still getting used to cabal...

Did you re-run configure after changing the cabal file?

Also, what ghc-pkg says has absolutely nothing to do with this; the
options Cabal passes completely override the ghc-pkg exposure flags.I
can hardly fault you for not knowing the answer to a Cabal FAQ, since
Cabal doesn't actually have a FAQ list yet.

You are running into the same problem as
http://www.haskell.org/pipermail/haskell-cafe/2007-August/030276.html,
and most of my explanation there applies here.

Stefan


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


[Haskell-cafe] trouble building regex-base 0.91 on ghc 6.7

2007-08-17 Thread Thomas Hartman
I'm trying to build the latest regex base, which is required for the other 
regex packages under ghc 6.7

It complains that it can't find Data.Sequence, because it's in a hidden 
module containers. I added containers to the cabal depends as can be seen 
in the grep below.

And containers isn't hidden when I do ghc-pkg list.

What gives?

Still getting used to cabal...

thomas.


[EMAIL PROTECTED]:~/installs/regex-base-0.91>runghc Setup.hs build
Preprocessing library regex-base-0.91...
Building regex-base-0.91...

Text/Regex/Base/RegexLike.hs:47:17:
Could not find module `Data.Sequence':
  it is a member of package containers-0.1, which is hidden

[EMAIL PROTECTED]:~/installs/regex-base-0.91>grep -i containers 
regex-base.cabal
Build-Depends:  base >= 2.0, mtl, containers 

[EMAIL PROTECTED]:~/installs/regex-base-0.91>ghc-pkg list
/usr/local/lib/ghc-6.7.20070816/package.conf:
Cabal-1.1.7, HUnit-1.1.1, QuickCheck-1.0.1, array-0.1,
arrows-0.2.1, base-2.1, bytestring-0.1, cgi-3001.1.5,
containers-0.1, directory-1.0, fgl-5.4.1, filepath-1.0,
(ghc-6.7.20070816), haskell-src-1.0.1, haskell98-1.0, hpc-0.5,
html-1.0.1, mtl-1.0.1, network-2.0.1, old-locale-1.0, old-time-1.0,
packedstring-0.1, parallel-1.0, parsec-2.0, pretty-1.0,
process-1.0, random-1.0, readline-1.0, regex-base-0.72, rts-1.0,
stm-2.1, template-haskell-0.1, unix-2.0, xhtml-3000.0.2

---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Basic question....

2007-08-17 Thread Bryan Burgers
On 8/17/07, rodrigo.bonifacio <[EMAIL PROTECTED]> wrote:
> Hi all.
>
> I want to create the following polymorphic type (EnvItem) that we can apply 
> two functions (envKey and envValue). I tried the following:
>
> > type Key = String
>
> > data EnvItem a = EnvItem (Key, a)
>
> > envKey :: EnvItem (Key, a) -> String
> > envKey EnvItem (key, value) = key
>
> > envValue :: EnvValue(Key, a) -> a
> > envValue EnvItem (key, value) = value
>
> But this is resulting in the error: [Constructor "EnvItem" must have exactly 
> 1 argument in pattern]
>
> I think this is a very basic problem, but I don't know what is wrong.
>
> Regards,
>
> Rodrigo.

In addition to what others have already said, I'd like to point out
that you do not really need a tuple in your data item.

> data EnvItem a = EI Key a

> envKey :: EnvItem a -> Key
> envKey (EI key _) = key

> envValue :: EnvValue a -> a
> envValue (EI _ value) = value

Also, you made a distinction between 'Key' and 'String', which is
good. But then in 'envKey', you used 'String' in the signature instead
of 'Key'.That's a little confusing, and also should you ever want to
change the representation of 'Key', you would then have to change the
signature of envKey.

Just my two cents,

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


[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread apfelmus

Justin Bailey wrote:

apfelmus wrote:


Extracting the head and tail of  ss  with a let statement could lead to
  a huge unevaluated expression like

   rest = tail (tail (tail (...)))


Even though they are probably forced, would breaking the head and tail
apart via pattern-matching or a case statement avoid building up that
unevaluated expression?


Yes, absolutely, since pattern matching has to force the scrutinee in 
order to choose the matching case. In contrast, a let statement


  let (x:xs) = expr in ...

simply assumes that  expr  is of the form (x:xs) but does not force it 
and check whether that's really the case. Of course, this may turn out 
as pattern match later on as soon as  x  is demanded but  expr  was 
initially the empty list.


In your case, the test  null ss  forces  ss  and checks whether the 
let-pattern is ok. So, you basically end up doing what a case expression 
would do. In other words, the situation is more "they are most likely 
forced" than "they are probably forced" and it's just a matter of 
convenience to choose one over the other.


But there are certain situations where you can check/prove differently 
that the let pattern never fails and where such a lazy pattern is wanted.


Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread Justin Bailey
On 8/17/07, apfelmus <[EMAIL PROTECTED]> wrote:

> Extracting the head and tail of  ss  with a let statement could lead to
>   a huge unevaluated expression like
>
>rest = tail (tail (tail (...)))

Even though they are probably forced, would breaking the head and tail
apart via pattern-matching or a case statement avoid building up that
unevaluated expression?

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


Re: [Haskell-cafe] Diagnosing stack overflow

2007-08-17 Thread Justin Bailey
On 8/16/07, Matthew Brecknell <[EMAIL PROTECTED]> wrote:
> However, it's possible that your use of this function is forcing
> evaluation of a deeply-nested thunk you've created somewhere else (as
> print does in the foldl example).

Thank you for the detailed and helpful reply. I was led to this
function by the vanilla profiling, which showed that it had the
highest percentage of allocations. Now I'm thinking I'll look at the
functions up the call stack to see which might be building up the
thunk. Would "retainer profiling" help me see what was building up
this large thunk/closure?

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


Re: [Haskell-cafe] Basic question....

2007-08-17 Thread Brent Yorgey
On 8/17/07, rodrigo.bonifacio <[EMAIL PROTECTED]> wrote:
>
> Hi all.
>
> I want to create the following polymorphic type (EnvItem) that we can
> apply two functions (envKey and envValue). I tried the following:
>
> > type Key = String
>
> > data EnvItem a = EnvItem (Key, a)
>
> > envKey :: EnvItem (Key, a) -> String
> > envKey EnvItem (key, value) = key
>
> > envValue :: EnvValue(Key, a) -> a
> > envValue EnvItem (key, value) = value
>
> But this is resulting in the error: [Constructor "EnvItem" must have
> exactly 1 argument in pattern]
>
> I think this is a very basic problem, but I don't know what is wrong.
>
> Regards,
>
> Rodrigo.


By the way, I would suggest giving the data type and constructor different
names:

data EnvItem a = EI (Key, a)

You do often see people use the same name for both, but that can be
confusing since they are really two different things.  The envKey function
(for example) would now be written like this:

envKey :: EnvItem a -> Key
envKey (EI (key, _)) = key

The difference between the parameter type (EnvItem a) and a pattern to match
the shape of such a value (EI (key, _)) is now much clearer: whatever is on
the left side of the data declaration is the type, and goes in type
signatures; whatever is on the right side describes the shape of values of
that type, and is used to construct or deconstruct (through
pattern-matching) such values.  This way it is much harder to make mistakes
like (for example) putting EnvItem (Key, a) in the type signature instead of
EnvItem a.

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


Re: [Haskell-cafe] Looking at program execution

2007-08-17 Thread Thomas Hartman
or actually just...

[EMAIL PROTECTED]:~>cat test.hs
import Debug.Trace

foo = foldl (\first second ->
  trace ( ( show first) ++ ("+") ++ (show second ) )
  ( first + second) ) 0 [1,2,3]

[EMAIL PROTECTED]:~>ghc -e foo test.hs
0+1
1+2
3+3
6
[EMAIL PROTECTED]:~>

is probably better




Thomas Hartman <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
08/17/2007 10:52 AM

To
haskell-cafe@haskell.org, [EMAIL PROTECTED]
cc

Subject
Re: [Haskell-cafe] Looking at program execution







[EMAIL PROTECTED]:~>cat test.hs 
import Debug.Trace 

foo = foldl (\first second -> 
  (trace ( "first: " ++ ( show first) ) first) 
  + 
  (trace ( "second: " ++ (show second) ) second) ) 0 [1,2,3] 

bar = foldl (+) 

traceIt x = trace ("\nTraceIt:\n"++show x++"\n") x 
[EMAIL PROTECTED]:~>ghc -e foo test.hs 
first: 0 
second: 1 
first: 1 
second: 2 
first: 3 
second: 3 
6 
[EMAIL PROTECTED]:~> 

hope this helps. 



Ian Duncan <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED] 
08/16/2007 08:20 PM 


To
haskell-cafe@haskell.org 
cc

Subject
[Haskell-cafe] Looking at program execution








Is there any way to view the steps that a haskell program goes 
through step by step?
I'm thinking something similar to what I've seen in things I've been 
reading. For example:
foldl (+) 0 [1..10]
=> (0+1)
=> ((0+1)+2)
=> (((0+1)+2)+3)
=> etc.
I've seen these sorts of line-by-line execution steps, but I was 
curious if there was any way to simply type in a function and its 
arguments and have ghci or hugs or something print out this sort of 
visual representation of what's going on. Anyone know of something 
like this?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


---

This e-mail may contain confidential and/or privileged information. If you 

are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Very fast searching of byte strings

2007-08-17 Thread ChrisK
Post the the library mailing list at [1] is the Boyer-Moore algorithm
implemented for strict and lazy bytestrings (and combinations thereof).  It
finds all the overlapping instances of the pattern inside the target.

I have performance tuned it.  But the performance for searching a strict
bytestring is better then for a lazy bytestring (even if they only had a single
strict chunk), which almost certainly means I was not clever enough to get GHC
to produce the optimal code.

There is much more description in the module's haddock header.

Hopefully Don or other ByteString experts/maintainers can tweak this even 
further.

Also at [1] is a Knuth-Morris-Pratt module which find non-overlapping
instances and is slightly slower on my benchmarks.

Happy Searching,
  Chris Kuklewicz

[1] http://www.haskell.org/pipermail/libraries/2007-August/007987.html

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


Re: [Haskell-cafe] Looking at program execution

2007-08-17 Thread Thomas Hartman
[EMAIL PROTECTED]:~>cat test.hs
import Debug.Trace

foo = foldl (\first second ->
  (trace ( "first: " ++ ( show first) ) first)
  +
  (trace ( "second: " ++ (show second) ) second) ) 0 [1,2,3]

bar = foldl (+)

traceIt x = trace ("\nTraceIt:\n"++show x++"\n") x
[EMAIL PROTECTED]:~>ghc -e foo test.hs
first: 0
second: 1
first: 1
second: 2
first: 3
second: 3
6
[EMAIL PROTECTED]:~>

hope this helps.




Ian Duncan <[EMAIL PROTECTED]> 
Sent by: [EMAIL PROTECTED]
08/16/2007 08:20 PM

To
haskell-cafe@haskell.org
cc

Subject
[Haskell-cafe] Looking at program execution






Is there any way to view the steps that a haskell program goes 
through step by step?
I'm thinking something similar to what I've seen in things I've been 
reading. For example:
foldl (+) 0 [1..10]
=> (0+1)
=> ((0+1)+2)
=> (((0+1)+2)+3)
=> etc.
I've seen these sorts of line-by-line execution steps, but I was 
curious if there was any way to simply type in a function and its 
arguments and have ghci or hugs or something print out this sort of 
visual representation of what's going on. Anyone know of something 
like this?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] defining last using foldr

2007-08-17 Thread Kurt Hutchinson
On 8/16/07, ok <[EMAIL PROTECTED]> wrote:
> We're going to have to keep track of whether we have a last element
> or not.  The obvious candidate for this is Maybe x.  Initially there
> is no element, Nothing.
> f x Empty = Just x
> f x (Just y) = Just y
> This picks up a new value (x) when there wasn't one (Nothing) and
> keeps the old last element (Just y) when there was one (Just y).
> But this gives us a Maybe x, when we want an x, so we'll have to finish
> off with a fromJust.
>
> last = fromJust . foldr f Nothing
>where f _ r@(Just _) = r
>  f x Nothing= Just x

I had this idea as well, but the questioner said the chapter with the
exercise preceded any use of Maybe, although I admit my suggestion of
using foldr to compose a processing function is more complicated for a
beginner. Here's a way to use the above idea without Maybe:

myLast = head . foldr f []
  where
f x [] = [x]
f _ [x] = [x]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Basic question....

2007-08-17 Thread Chaddaï Fouché
17 Aug 2007 14:44:28 +0100, Jon Fairbairn <[EMAIL PROTECTED]>:
> Why not
>
> > data EnvItem a = EnvItem {key:: Key, value:: a}

It's the real solution, but I feel it was worthwhile to underscore the
other mistakes (often encountered by the newbies) in types and
parameters.

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


[Haskell-cafe] Re: Basic question....

2007-08-17 Thread Jon Fairbairn
"Chaddaï Fouché" <[EMAIL PROTECTED]> writes:

> Not only does you lack some parens around your patterns, your function
> types are wrong :
> 
> type Key = String
> 
> data EnvItem a = EnvItem (Key, a)
> 
> envKey :: EnvItem a -> String
> envKey (EnvItem (key, value)) = key
> 
> envValue :: EnvItem a -> a
> envValue (EnvItem (key, value)) = value

Why not

> data EnvItem a = EnvItem {key:: Key, value:: a}

?

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


[Haskell-cafe] Re: Compile-time v run-time

2007-08-17 Thread Jon Fairbairn
Kim-Ee Yeoh <[EMAIL PROTECTED]> writes:
> Jon Fairbairn wrote:
> > Something I've wanted to experiment with for a long time and
> > never got round to is writing CAFs back to the load module
> > at the end of a run (if they're small enough or took a long
> > time to evaluate). 

> If RAM was treated as an extension of non-volatile 
> storage instead of the other way round, we'd already 
> be there.

Not exactly

> Put another way, would "suspending" program to 
> disk achieve the same results?

No, because the state in RAM includes not only CAFs but data
that depends on the history of the present run.  If you only
write CAFs back, running the modified module gives the same
effect as running the unmodified version.  Resuming a
suspended programme has the effect of continuing from where
you left off.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] Basic question....

2007-08-17 Thread Chaddaï Fouché
Not only does you lack some parens around your patterns, your function
types are wrong :

type Key = String

data EnvItem a = EnvItem (Key, a)

envKey :: EnvItem a -> String
envKey (EnvItem (key, value)) = key

envValue :: EnvItem a -> a
envValue (EnvItem (key, value)) = value

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


[Haskell-cafe] Re: I'm stuck in my thought experiment

2007-08-17 Thread Al Falloon

Levi Stephen wrote:

Hi,

Apologies for a long post that may not be totally clear. I was thinking 
through
a problem and how the data might be represented in Haskell. I'm now 
stuck and

frustrated. Now, I'm not even sure whether I'm on the right track (I might
still be thinking too OO). Suggestions/ideas would be much appreciated.

I was imagining a drag and drop web page designer. There are a bunch of
Widgets (e.g., BlogWidget, TextWidget, MenuWidget, etc) that the user can
place on the page.

Along with these are layout/container widgets (e.g., ColumnLayoutWidget) 
that can contain

other widgets.

I'm looking at a data structure that would allow this to be represented 
in Haskell,

so I'm keeping in mind that these won't be written in code, but generated
on the fly somehow (e.g., from a database or file).


Maybe I am misunderstanding your requirements, but it seems to me that 
the simplest solution would be best in this case:


data Widget = BlogWidget [Article]
| TextWidget String
| MenuWiget Menu
| Rows Spacing [Widget]
| Columns Spacing [Widget]

You can also add a type parameter if you want to be able to carry around 
extra metadata about pages, or you could even parameterize the Article 
and Menu types if you want to be able to extend them separately or if 
you want to ensure your layout algorithms don't depend on widget 
contents by keeping their type abstract.




So, my thoughts were along the lines of something like:

class Widget a where
 render :: a -> Html

-- A page has a title and a Widget.
-- I know this isn't valid Haskell, but I'm not sure how to specify what I
-- want here. (existential types?)
data Page = Page String Widget

data TextWidget = TextWidget String
instance Widget TextWidget 

-- An example layout widget
data ColumnLayoutWidget = ColumnLayoutWidget [Widget]
instance Widget ColumnLayoutWidget ...
etc...

So, entire pages might be represented something like:

Page "Main" (ColumnLayoutWidget [MenuWidget, TextWidget mainPageText])
Page "About" (ColumnLayoutWidget [MenuWidget, TextWidget aboutPageText])


This code seems to indicate that you want to be able to extend the 
widget types without changing this source file. This is a good goal, but 
it may not be worth the extra complexity.


Also, this looks a lot like the Composite pattern from OO. A rule of 
thumb that I use is: "if I would do this with inheritance in OO, I 
probably want a variant in FP". Since Composite depends on the 
inheritance of the composite object type, I would probably look to use a 
 single data type with multiple constructors for the different 
compisites like the Widget type above.


If I wanted to develop the widgets themselves separately from the 
layout, I would probably do something like this:


class Widget a where
render :: a -> Html
bbox :: a -> Size

type Layout = forall a. Widget a => Widget a
| Rows Spacing [Layout]
| Columns Spacing [Layout]
| Grid Spacing [[Layout]]

type Page = Page String Layout

renderLayout :: Layout -> Html

renderPage :: Page -> Html

Where I get stuck, is I want to extract layout information into a parent 
page.
This would allow global changes such as adding a header image to the 
above pages

to be done once only.


By making the layout type separate from the widgets themselves, it 
allows you to examine the layout and do any transformations you want 
without having to know anything about the widgets.



So I want to be able to have something like:

layout = Page "Main" (ColumnLayoutWidget [MenuWidget, ??? ])
mainPage = ChildPage layout [TextWidget mainPageText]
aboutPage = ChildPage layout [TextWidget aboutPageText]

So, each page is it's layout/parent page, with additional widgets 
inserted/added.


So you want some sort of wildcard element that can be substituted in 
later? Maybe I am misunderstanding your requirement, but if thats the 
behavior you want, you should check out the term-level evaluators for 
lambda calculus for inspiration on substitution, but I expect your 
requirement may be simpler than that.




The issue becomes, given a parent page and the customized content for 
the child page,

what is the best way to insert the customized content at the right point?

Might a tree like structure be useful? But, how do you work out where in 
the tree
child content gets added? Store a traversal with each sub tree of child 
page content

that basically says 'insert here'?


This is probably a good use for a zipper (a kind of functional 
iterator). http://en.wikibooks.org/wiki/Haskell/Zippers that way you can 
pass around a value that means "right here", and its clear where the 
substitution will happen.


Another good zipper war story is from xmonad: 
http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/17


It might be simple to have a PlaceHolderWidget. Then insertions of the 
child page

content happens at each of those widgets.


This just gets trickier if I start considering multipl

Re: [Haskell-cafe] Basic question....

2007-08-17 Thread Janis Voigtlaender
- Ursprüngliche Nachricht -
Von: "rodrigo.bonifacio" <[EMAIL PROTECTED]>
Datum: Freitag, August 17, 2007 3:11 pm
Betreff: [Haskell-cafe] Basic question

> Hi all.
> 
> I want to create the following polymorphic type (EnvItem) that we 
> can apply two functions (envKey and envValue). I tried the following:
> 
> > type Key = String
> 
> > data EnvItem a = EnvItem (Key, a)
> 
> > envKey :: EnvItem (Key, a) -> String
> > envKey EnvItem (key, value) = key
> 
> > envValue :: EnvValue(Key, a) -> a
> > envValue EnvItem (key, value) = value
> 
> But this is resulting in the error: [Constructor "EnvItem" must 
> have exactly 1 argument in pattern]
> 
> I think this is a very basic problem, but I don't know what is wrong.

You are simply missing some brackets:

> envKey :: EnvItem (Key, a) -> String
> envKey (EnvItem (key, value)) = key

> envValue :: EnvValue(Key, a) -> a
> envValue (EnvItem (key, value)) = value

Ciao, Janis.



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


Re: [Haskell-cafe] Basic question....

2007-08-17 Thread Brandon S. Allbery KF8NH


On Aug 17, 2007, at 9:11 , rodrigo.bonifacio wrote:


envKey :: EnvItem (Key, a) -> String
envKey EnvItem (key, value) = key



envValue :: EnvValue(Key, a) -> a
envValue EnvItem (key, value) = value


But this is resulting in the error: [Constructor "EnvItem" must  
have exactly 1 argument in pattern]


You need to parenthesize the constructor.

envValue (EnvItem (_,value)) = value

(The _ indicates that you're not using that item, rather than giving  
it a name that won't be used.)


Why do you need to do this?  Because you can pass functions around,  
and a constructor is a function.  But your type says you don't want a  
bare function there, so the compiler complains.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [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


[Haskell-cafe] Basic question....

2007-08-17 Thread rodrigo.bonifacio
Hi all.

I want to create the following polymorphic type (EnvItem) that we can apply two 
functions (envKey and envValue). I tried the following:

> type Key = String

> data EnvItem a = EnvItem (Key, a)

> envKey :: EnvItem (Key, a) -> String
> envKey EnvItem (key, value) = key

> envValue :: EnvValue(Key, a) -> a
> envValue EnvItem (key, value) = value

But this is resulting in the error: [Constructor "EnvItem" must have exactly 1 
argument in pattern]

I think this is a very basic problem, but I don't know what is wrong.

Regards,

Rodrigo.

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


Re: [Haskell-cafe] So far, so good! Until... (Haskell 98 Report questions)

2007-08-17 Thread Christopher L Conway
Ian,

This is all programming language parsing jargon. If the Wikipedia
doesn't help (try http://en.wikipedia.org/wiki/Formal_grammar), I
recommend the first few chapters of Aho, Sethi, & Ullman's "Compilers:
Principles, Techniques, and Tools" aka "the dragon book", or any good
book on compilers, e.g., Andrew Appel's "Modern Compiler
Implementation".

Chris

On 8/17/07, Ian Duncan <[EMAIL PROTECTED]> wrote:
>
> ... I hit Chapter 3 and started reading about expressions.
>
> *If you are able to answer any of these questions, please send me an email.
> I am very lost and confused in this section, so even one answered question
> may help greatly.*
>
> I actually decided to sit down and figure out the Haskell 98 Report today.
> Everything was going well until I began Chapter 3. Here's the section that
> has me baffled:
>  "In the syntax that follows, there are some families of nonterminals
> indexed by precedence levels (written as superscript). Similarly, the
> nonterminals op, varop, and conop may have a double index: a letter l, r, or
> n for left-, right- or non-associativity and a precedence level. A
> precedence-level variable i ranges from 0 to 9; an associativity variable,
> a, varies over {l,r,n}. For example, aexp ->  ( exp^(i+1) qop^(a,i) )
> actually stands for 30 productions, with 10 substitutions for i and 3 for
> a." *note that the "^" was used to indicate superscript.
>
> So here's my list of questions so far:
> 1. What are nonterminals?
> 2. What are productions and substitutions?
>
> I tried the dictionary and wikipedia, but neither were very helpful in
> defining those terms.
>
> Next, it says:
>  exp -> exp^0 :: [context=>] type   (expression type signature)
>   |  exp^0
>  exp^i -> exp^(i+1) [qop^(n,i) exp^(i+1)]
> |   lexp^i
> |   rexp^i
>  ...
> From there it continues with more syntax stuff, but I'll stop there for the
> sake of not typing too much. So here are some questions about this section:
> 1. What the heck is going on?
> 2. How is an expression with a precedence of i considered to be an
> expression of i+1?
> 3. Within the ... section it mentions lexp and rexp. Do those stand for
> left-associative expressions and right-associative expressions respectively?
>
> I understand the concept of fixity when I see it mentioned in code, but I
> truly have no idea what 3.0 is talking about. Can anyone shed some light on
> any of this? I'm still in high school, so if anyone could please explain it
> to me in layman's terms primarily, or provide some resources explaining more
> complex terms, It would be greatly appreciated.
>
> Thanks a bunch!
>  Ian Duncan
> ___
> 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] So far, so good! Until... (Haskell 98 Report questions)

2007-08-17 Thread Andy Gimblett
On Fri, Aug 17, 2007 at 04:50:02AM -0700, Ian Duncan wrote:
>
> So here's my list of questions so far:
> 1. What are nonterminals?
> 2. What are productions and substitutions?
> [snip]

Sounds to me like you want a book on language design, grammars,
parsing, etc. :-)

There are many good ones out there, but a quite nice, free, and (as it
happens, though it's irrelevant for this question) Haskellish example
is "Grammars and Parsing" by Jeuring & Swierstra (PDF, 1.2MB):

http://www.cs.uu.nl/docs/vakken/gont/diktaat.pdf

(Ignore the Dutch foreword, the rest is in English).  Chapter 2
answers the questions asked above, with copious examples and
exercises.

Hope this helps,

-Andy

-- 
Andy Gimblett
Computer Science Department
University of Wales Swansea
http://www.cs.swan.ac.uk/~csandy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] So far, so good! Until... (Haskell 98 Report questions)

2007-08-17 Thread Ian Duncan

... I hit Chapter 3 and started reading about expressions.

*If you are able to answer any of these questions, please send me an  
email. I am very lost and confused in this section, so even one  
answered question may help greatly.*


I actually decided to sit down and figure out the Haskell 98 Report  
today. Everything was going well until I began Chapter 3. Here's the  
section that has me baffled:
	"In the syntax that follows, there are some families of nonterminals  
indexed by precedence levels (written as superscript). Similarly, the  
nonterminals op, varop, and conop may have a double index: a letter  
l, r, or n for left-, right- or non-associativity and a precedence  
level. A precedence-level variable i ranges from 0 to 9; an  
associativity variable, a, varies over {l,r,n}. For example, aexp ->   
( exp^(i+1) qop^(a,i) ) actually stands for 30 productions, with 10  
substitutions for i and 3 for a." *note that the "^" was used to  
indicate superscript.


So here's my list of questions so far:
1. What are nonterminals?
2. What are productions and substitutions?

I tried the dictionary and wikipedia, but neither were very helpful  
in defining those terms.


Next, it says:
exp -> exp^0 :: [context=>] type   (expression type signature)
 |  exp^0
exp^i -> exp^(i+1) [qop^(n,i) exp^(i+1)]
   |   lexp^i
   |   rexp^i
...
From there it continues with more syntax stuff, but I'll stop there  
for the sake of not typing too much. So here are some questions about  
this section:

1. What the heck is going on?
2. How is an expression with a precedence of i considered to be an  
expression of i+1?
3. Within the ... section it mentions lexp and rexp. Do those stand  
for left-associative expressions and right-associative expressions  
respectively?


I understand the concept of fixity when I see it mentioned in code,  
but I truly have no idea what 3.0 is talking about. Can anyone shed  
some light on any of this? I'm still in high school, so if anyone  
could please explain it to me in layman's terms primarily, or provide  
some resources explaining more complex terms, It would be greatly  
appreciated.


Thanks a bunch!
Ian Duncan___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Compile-time v run-time

2007-08-17 Thread Kim-Ee Yeoh

If RAM was treated as an extension of non-volatile 
storage instead of the other way round, we'd already 
be there.

Put another way, would "suspending" program to 
disk achieve the same results?


Jon Fairbairn wrote:
> 
> Something I've wanted to experiment with for a long time and
> never got round to is writing CAFs back to the load module
> at the end of a run (if they're small enough or took a long
> time to evaluate).  Has anyone tried this? (It would have a
> jolly entertaining effect on benchmark pages!).
> 
> The logical extension of this would be that compiling a
> programme did the typechecking and then just wrote the
> binary equivalent of 'evaluate $ code-generate "...lambda
> expressions from programme text..."' into the load-module.
> If you never run the programme, this would be quicker. If
> you only run the programme once, it would take about the
> same time, and running it several times would be quicker --
> very much so if it didn't depend on any run-time data.
> 

-- 
View this message in context: 
http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12197690
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Kim-Ee Yeoh


Lennart Augustsson wrote:
> 
> On 8/17/07, Kim-Ee Yeoh <[EMAIL PROTECTED]> wrote:
>> How much static evaluation do you want to see
>> in Haskell?
> 
> I'd like to see as much static evaluation as is practically possible.
> 

Yes but not in (the language formally defined as) Haskell. Not 
even in {your favorite Haskell compiler/interpreter} without -O. 
With -O by all means let her rip.

Incidentally, GHC's type checker is Turing complete. You 
already have as much static evaluation as is practically possible. 
You already knew that.


Lennart Augustsson wrote:
> 
> And as a previous poster showed, ghc does concatenate strings.
> 

And Haskell (as in the current language definition) does not.
I was talking about Haskell.

Having said that, I'll concede there may be room for more than 
one language here. I want syntax transparently reflecting
straightforward if slowpoke operational semantics. You want 
fast, tight programs. I want fast, tight programs too, but 
not by giving up the former.

-- 
View this message in context: 
http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12197224
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread L.Guo
Hi.

My plan is just add some *unusable* data to make diagonal grid normally.

Here this is.

p011_input = input ++ (transpose input) ++ diagInput ++ diagInputT
  where diagInput = p011_toDiag input
diagInputT = p011_toDiag . (map reverse) $ input
input = [ [08,02,22,97,38,15,00,40,00,75,04,05,07,78,52,12,50,77,91,08],
  [49,49,99,40,17,81,18,57,60,87,17,40,98,43,69,48,04,56,62,00],
  ... ,
  [01,70,54,71,83,51,54,69,16,92,33,48,61,43,52,01,89,19,67,48] 
]
p011_toDiag = (map remove) . transpose . (map append) . addIndex
  where addIndex = zip [0..]
append (n,y) = replicate n (-1) ++ y ++ replicate (19-n) (-1)
remove = filter (-1/=)
p011_toGroups x = case x of
  (a:b:c:d:xs)  -> [a,b,c,d] : p011_toGroups (b:c:d:xs)
  _ -> []
p011_solve = putStrLn . show $ (foldl1 max) . (map product) . concat . (map 
p011_toGroups) $ p011_input


--   
L.Guo
2007-08-17

-
From: Ronald Guida
At: 2007-07-20 11:39:50
Subject: [Haskell-cafe] Hints for Euler Problem 11

To handle the diagonals, my plan is to try to extract each diagonal as
a list of elements and put all the diagonals into a list; then I can
use maxHorizontal.

I came up with this function to try to extract the main diagonal.

 > getDiag :: [[a]] -> [a]
 > getDiag = map (head . head) . iterate (tail . map tail)

The problem is, this function doesn't work unless I have an infinite
grid.


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


Re: [Haskell-cafe] Re: Bathroom reading

2007-08-17 Thread Kim-Ee Yeoh


ok-4 wrote:
> 
> Someone mentioned the "Blow your mind" page.
> One example there really caught my attention.
>   "1234567" => ("1357","246")
>   foldr (\a ~(x,y) -> (a:y,x)) ([],[])
> 
> I've known about lazy match since an early version of the Haskell
> report, but have never actually used it.  Last night, looking at
> that example, the lights went on and I finally grokked why it's
> there and understood when/why I might use it myself.
> 

Don't you want an infinite list to illustrate the necessity 
of laziness?

-- 
View this message in context: 
http://www.nabble.com/Bathroom-reading-tf4267956.html#a12196642
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Compile-time v run-time

2007-08-17 Thread Jon Fairbairn
I wrote:
> the compile-time/run-time dichotomy is only relevant when a
> value depends on data only available at run-time.

Something I've wanted to experiment with for a long time and
never got round to is writing CAFs back to the load module
at the end of a run (if they're small enough or took a long
time to evaluate).  Has anyone tried this? (It would have a
jolly entertaining effect on benchmark pages!).

The logical extension of this would be that compiling a
programme did the typechecking and then just wrote the
binary equivalent of 'evaluate $ code-generate "...lambda
expressions from programme text..."' into the load-module.
If you never run the programme, this would be quicker. If
you only run the programme once, it would take about the
same time, and running it several times would be quicker --
very much so if it didn't depend on any run-time data.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


[Haskell-cafe] Re: Hints for Euler Problem 11

2007-08-17 Thread Jon Fairbairn
Kim-Ee Yeoh <[EMAIL PROTECTED]> writes:

> Aaron Denney wrote:
> > I find the first far more readable.  The compiler should be able to
> > assemble it all at compile time, right?
> > 
> 
> 'Course not. The (++) function like all Haskell functions is only a
> /promise/ to do its job.

I find this comment rather strange.  One of the beauties of
a pure language (especially a lazy one) is that there is no
requirement for evaluation to take place at at any
particular time as long as it's done before it's needed. So
the compile-time/run-time dichotomy is only relevant when a
value depends on data only available at run-time.

Given that "foo "++"bar" can be evaluated at compile time
and there are advantages and no disadvantages, it should be
evaluated at compile time. In general, I don't think we
should clutter the language with syntax for things for which
there has to be a more general mechanism; including string
breaks in the language was a mistake.

Compare

   "thing1\n\
   \thing2\n\
   \thing3\n"++
   otherThing++
   "penultimate thing\n\
   \last thing\n"

with

   "thing1\n"++
   "thing2\n"++
   "thing3\n"++
   otherThing++
   "penultimate thing\n"++
   "last thing\n"

What /is/ the advantage of the former?

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Kim-Ee Yeoh

The compiler dumps are illuminating, thank you. 

I'm afraid I don't always compile under -O. In fact I never
debug with -O. I see now what I'm missing.

(Pain, grief, despair.)


Ketil Malde wrote:
> 
> On Thu, 2007-08-16 at 12:50 -0700, Kim-Ee Yeoh wrote:
>> Aaron Denney wrote:
>> > The compiler should be able to
>> > assemble it all at compile time, right?
>> 
>> 'Course not. The (++) function like all Haskell functions is only a
>> /promise/ to do its job. What does "assembling at compile time"
>> mean here:
>> 
>> s = "I will not write infinite loops " ++ s
> 
>   % cat C.hs
> 
>   module Test where
> 
>   x = "Foo" ++ "Bar"
>   y = "Zot" ++ y
> 
>   % ghc -ddump-simpl C.hs
> 
>    Tidy Core 
>   Test.x :: [GHC.Base.Char]
>   [GlobalId]
>   []
>   Test.x =
> GHC.Base.++
>   @ GHC.Base.Char (GHC.Base.unpackCString# "Foo")
> (GHC.Base.unpackCString# "Bar")
> 
>   Rec {
>   Test.y :: [GHC.Base.Char]
>   [GlobalId]
>   []
>   Test.y = GHC.Base.++ @ GHC.Base.Char (GHC.Base.unpackCString# "Zot")
> Test.y
>   end Rec }
> 
> If I interpret it correctly, the compiler does approximately nothing -
> reasonably enough, since we didn't ask for optimization.  With -O:
> 
>   % ghc -ddump-simpl C.hs -O
> 
>    Tidy Core 
>   Rec {
>   Test.y :: [GHC.Base.Char]
>   [GlobalId]
>   [Str: DmdType]
>   Test.y = GHC.Base.unpackAppendCString# "Zot" Test.y
>   end Rec }
> 
>   Test.x :: [GHC.Base.Char]
>   [GlobalId]
>   [Str: DmdType]
>   Test.x = GHC.Base.unpackCString# "FooBar"
> 
> y gets turned into an unpackAppendCString#, which I can only presume is
> a sensible way to represent a cyclic list, while x gets concatenated
> compile-time.
> 

-- 
View this message in context: 
http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12196104
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Lennart Augustsson
It's very hard to tell if it's worth it or not.  Concatenating constant
strings will turn the string into WHNF, which might enable some other
transformation.  By having lots of little transformations that on their own
look worthless you can make big improvements.
I'd like to see as much static evaluation as is practically possible.

And as a previous poster showed, ghc does concatenate strings.

On 8/17/07, Kim-Ee Yeoh <[EMAIL PROTECTED]> wrote:
>
>
>
> Lennart Augustsson wrote:
> >
> > On 8/16/07, Kim-Ee Yeoh <[EMAIL PROTECTED]> wrote:
> >> 'Course not. The (++) function like all Haskell functions is only a
> >> /promise/ to do its job. What does "assembling at compile time"
> >> mean here:
> >>
> >> s = "I will not write infinite loops " ++ s
> >
> > But if the strings are all constant it's perfectly feasible to
> concatenate
> > them at compile time.
> >
>
> It's feasible and I might add that it isn't worth it. Not for just
> concatenation. How much static evaluation do you want to see
> in Haskell?
>
> --
> View this message in context:
> http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12195537
> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>
> ___
> 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


[Haskell-cafe] Re: Diagnosing stack overflow

2007-08-17 Thread apfelmus

Justin Bailey wrote:

-- Determines if the length of the strings in the list is longer than the given
-- count. If not, amount the list falls short is returned. Otherwise,
-- -1 indicates the prefix list is at least that long. If the count is zero and
-- the list is empty or just null strings, -1 is also returned.

>

prefixesAtLeast :: Int -> [S.ByteString] -> Int


While that doesn't help your stack overflow problem, it's not very 
haskellish to return magic numbers. A Maybe type is more appropriate here.



prefixesAtLeast !0 !ss
  | null ss = 0
  | all S.null ss = 0
  | otherwise = -1
prefixesAtLeast !n !ss = prefixesAtLeast' n ss
  where
  prefixesAtLeast' !n ss
| n < 0 = -1
| null ss = n
| otherwise =
let (!s : (!rest)) = ss
in
  prefixesAtLeast' (n - (S.length s)) rest


Extracting the head and tail of  ss  with a let statement could lead to 
 a huge unevaluated expression like


  rest = tail (tail (tail (...)))

but the null test are likely to force it. Also note that the case  n = 0 
is quite rare. In any case, I'd write the function as


  lengthExcess :: Int -> [S.ByteString] -> Maybe Int
  lengthExcess n ss
 | n <= 0= Nothing
 | otherwise = case ss of
[] -> Just n
(s:ss) -> lengthExcess (n - S.length s) ss

Note the that the function name is chosen to mnemonically match the 
result type Maybe Int, i.e. "the excess is Just 5 characters" or "the 
excess is Nothing".


Regards,
apfelmus

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


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Kim-Ee Yeoh


Lennart Augustsson wrote:
> 
> On 8/16/07, Kim-Ee Yeoh <[EMAIL PROTECTED]> wrote:
>> 'Course not. The (++) function like all Haskell functions is only a
>> /promise/ to do its job. What does "assembling at compile time"
>> mean here:
>>
>> s = "I will not write infinite loops " ++ s
> 
> But if the strings are all constant it's perfectly feasible to concatenate
> them at compile time.
> 

It's feasible and I might add that it isn't worth it. Not for just
concatenation. How much static evaluation do you want to see
in Haskell?

-- 
View this message in context: 
http://www.nabble.com/Hints-for-Euler-Problem-11-tf4114963.html#a12195537
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Hints for Euler Problem 11

2007-08-17 Thread Ketil Malde
On Thu, 2007-08-16 at 12:50 -0700, Kim-Ee Yeoh wrote:
> 
> Aaron Denney wrote:
> > 
> > On 2007-08-15, Pekka Karjalainen <[EMAIL PROTECTED]> wrote:
> >> A little style issue here on the side, if I may. You don't need to use
> >> (++) to join multiline string literals.
> >>
> >> text = "If you want to have multiline string literals \
> >>\in your source code, you can break them up with \
> >>\backslashes. Any whitespace characters between \
> >>\two backslashes will be ignored."
> > 
> > I find the first far more readable.  The compiler should be able to
> > assemble it all at compile time, right?
> > 
> 
> 'Course not. The (++) function like all Haskell functions is only a
> /promise/ to do its job. What does "assembling at compile time"
> mean here:
> 
> s = "I will not write infinite loops " ++ s

Let's check, shall we?  I've never used core before, but there's a first
time for everything:

  % cat C.hs

  module Test where

  x = "Foo" ++ "Bar"
  y = "Zot" ++ y


  % ghc -ddump-simpl C.hs

   Tidy Core 
  Test.x :: [GHC.Base.Char]
  [GlobalId]
  []
  Test.x =
GHC.Base.++
  @ GHC.Base.Char (GHC.Base.unpackCString# "Foo") (GHC.Base.unpackCString# 
"Bar")

  Rec {
  Test.y :: [GHC.Base.Char]
  [GlobalId]
  []
  Test.y = GHC.Base.++ @ GHC.Base.Char (GHC.Base.unpackCString# "Zot") Test.y
  end Rec }

If I interpret it correctly, the compiler does approximately nothing -
reasonably enough, since we didn't ask for optimization.  With -O:

  % ghc -ddump-simpl C.hs -O

   Tidy Core 
  Rec {
  Test.y :: [GHC.Base.Char]
  [GlobalId]
  [Str: DmdType]
  Test.y = GHC.Base.unpackAppendCString# "Zot" Test.y
  end Rec }

  Test.x :: [GHC.Base.Char]
  [GlobalId]
  [Str: DmdType]
  Test.x = GHC.Base.unpackCString# "FooBar"

y gets turned into an unpackAppendCString#, which I can only presume is
a sensible way to represent a cyclic list, while x gets concatenated
compile-time.

-k


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


Re: [Haskell-cafe] Collada, FBX, XML schemas and Haskell?

2007-08-17 Thread Radosław Grzanka
Hello,

2007/8/16, Peter Verswyvelen <[EMAIL PROTECTED]>:
> I wanted to do some experiments with HOpenGL, and one of the things I tried 
> is importing 3D models.
>
> So I searched for a library that could do that, but besides Frag, who uses 
> the limited MD3 format, I did not find anything useful. Has any work been 
> done on supporting that? Maybe just converting the 3D format into a series of 
> HOpenGL calls (tools like that exists for C)?

Some time ago I tried to write 'importer' for (full) MD2 format and
then MD5 format from Id Software. I gathered quite a bit information
about it and it should not be very complicated to support these format
(especially MD2).

Unfortunatly I hadn't had time to do that plus I'm Haskell newbie but
importing and animating MD5 models in Haskell has such a appeal to me!

I really encourage you to browse through MD2 specification. It is
really straightforward and ready to be rendered "out-of-the-box".
http://tfc.duke.free.fr/old/models/md2.htm
Plus many 3D software have exporter to MD2.

Cheers,
  Radek.

-- 
Codeside: http://codeside.org/
Przedszkole Miejskie nr 86 w Lodzi: http://www.pm86.pl/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe