[Haskell-cafe] Style

2007-08-24 Thread Arie Groeneveld
Hi,

I defined several functions for calculating the number
of trailing zero's of n!


tm = sum . takeWhile(0) . iterate f . f
   where f = flip div 5

tm1 n = sum . takeWhile(0) . map (div n . (5^)) $ [1..]
tm2 n = sum . takeWhile(0) . map (div n) $ iterate ((*)5) 5
tm3 = sum . takeWhile(0) . flip map (iterate ((*)5) 5) . div



Questions:

Which one is the most elegant one generally speaking?
Which one is most natural in Haskell?
Is there more 'beauty' to possible?


My personal choice is 'tm'.
I like 'tm3' (a revised version of tm2) in terms of
pointlessness and not having a 'where', but I think
it's a bit contrived because of the 'flip'.

Comments?



Thanks

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


Re: [Haskell-cafe] Style

2007-08-24 Thread Bjorn Bringert


On Aug 24, 2007, at 9:18 , Arie Groeneveld wrote:


Hi,

I defined several functions for calculating the number
of trailing zero's of n!


tm = sum . takeWhile(0) . iterate f . f
   where f = flip div 5

tm1 n = sum . takeWhile(0) . map (div n . (5^)) $ [1..]
tm2 n = sum . takeWhile(0) . map (div n) $ iterate ((*)5) 5
tm3 = sum . takeWhile(0) . flip map (iterate ((*)5) 5) . div



Questions:

Which one is the most elegant one generally speaking?
Which one is most natural in Haskell?
Is there more 'beauty' to possible?


My personal choice is 'tm'.
I like 'tm3' (a revised version of tm2) in terms of
pointlessness and not having a 'where', but I think
it's a bit contrived because of the 'flip'.

Comments?


Here's a much more inefficient version, but it has the merit of being  
very easy to understand:


tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product  
[1..n]


/Björn

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


Re: [Haskell-cafe] Help using CGIT

2007-08-24 Thread Bjorn Bringert

On Aug 23, 2007, at 3:34 , Rich Neswold wrote:


On 8/22/07, Ian Lynagh [EMAIL PROTECTED] wrote:
On Wed, Aug 22, 2007 at 01:27:00PM -0500, Rich Neswold wrote:

  newtype App a = App (ReaderT Connection (CGIT IO) a)
 deriving (Monad, MonadIO, MonadReader Connection)

 Unfortunately, when another module tries to actually use the  
monad, I
 get warnings about No instance for (MonadCGI App). I tried  
making an

 instance:

  instance MonadCGI App where
  cgiAddHeader = ?
  cgiGet = ?

You have three choices:

1:

2:

3:
Provide a single instance for App that does the whole thing:
instance MonadCGI App where
cgiAddHeader n v = App $ lift $ cgiAddHeader n v
cgiGet x = App $ lift $ cgiGet x
This one you would obviously have to change if you added a StateT.

Bingo! Method #3 works beautifully! I missed the using-lift-with- 
the-constructor permutation.


Thanks for your help!


I started writing a tutorial for Haskell web programming with the cgi  
package a while back, but haven't worked on it for a while, see  
http://www.haskell.org/haskellwiki/Practical_web_programming_in_Haskell
I haven't added it to the list of tutorials yet, since it's still  
rather incomplete.


The section on using CGIT is just a stub, perhaps you would like to  
contribute to it? See
http://www.haskell.org/haskellwiki/ 
Practical_web_programming_in_Haskell#Extending_the_CGI_monad_with_monad_ 
transformers


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


[Haskell-cafe] latest cabal conflict?

2007-08-24 Thread Luc TAESCH
when trying to build the latest cabal from darcs,
I got
[EMAIL PROTECTED]:~/src/cabinstall/cabal$ runghc Setup.lhs configure

Distribution/Simple.hs:110:7:
Could not find module `System.FilePath':
  it was found in multiple packages: filepath-1.0 FilePath-0.11
[EMAIL PROTECTED]:~/src/cabinstall/cabal$

sound like a conflict , i still have ghc 6.6, not 6.6.1.

what should I do ?
hide FilePath-0.11 in Distribution/Simple.hs imports ? ( and for all othe files?
any way to just have FilePath out of the way via a Cabal statement?

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


Re: [Haskell-cafe] Style

2007-08-24 Thread Arie Groeneveld
Bjorn Bringert wrote:

 
  Here's a much more inefficient version, but it has the merit of being
  very easy to understand:
 
  tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n]
 
   
You're rigth. I came up with that one too the first time. But for large
value's of n
it takes too much time. You may improve that (time) by using another
product
formula:

*Main length $ takeWhile (=='0') $ reverse $ show $ foldl' (*) 1 [1..3]
7498
(0.96 secs, 790685000 bytes)

*Main length $ takeWhile (=='0') $ reverse $ show $ product [1..3]
7498
(4.05 secs, 792259140 bytes)

But:

*Main tm 3
7498
(0.00 secs, 524924 bytes)


Thanks

@@i





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


Re: [Haskell-cafe] Style

2007-08-24 Thread Henning Thielemann


On Fri, 24 Aug 2007, Arie Groeneveld wrote:


I defined several functions for calculating the number
of trailing zero's of n!


tm = sum . takeWhile(0) . iterate f . f
  where f = flip div 5


This is very elegant! You could also inline 'f'

tm4 = sum . takeWhile(0) . tail . iterate (flip div 5)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Haddock: documenting parameters of functional arguments

2007-08-24 Thread Simon Marlow

Henning Thielemann wrote:

I like to write documentation comments like

fix ::
  (   a {- ^ local argument -}
   - a {- ^ local output -} )
  - a {- ^ global output -}

but Haddock doesn't allow it. Or is there a trick to get it work?


Haddock only supports documenting the top-level arguments of a function 
right now.


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


Re: [Haskell-cafe] Style

2007-08-24 Thread Mirko Rahn



tm = sum . takeWhile(0) . iterate f . f
   where f = flip div 5


Quite nice. I like

tm5 0 = 0
tm5 n = let q = div n 5 in q + tm5 q

This version corresponds to what I'm think when parsing |tm|, so I wrote 
it down directly.


Also possible

tm6 = sum . unfoldr ( \ n - case div n 5 of
  0 - mzero
  q - return (q,q)
)

I tend to not use |iterate|, when it is known in advance, which prefix 
of the so constructed infinite list is used.


/BR

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: Remember the future

2007-08-24 Thread Simon Peyton-Jones
| From the ghc manual:
|
| ---
| 7.3.3. The recursive do-notation
| ...

|
| It is unfortunate that the manual does not give the translation rules, or at
| least the translation for the given example.

Hmm.  OK.  I've improved the manual with a URL to the main paper
http://citeseer.ist.psu.edu/erk02recursive.html
which is highly readable. And I've given the translation for the example as you 
suggest

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


Re: [Haskell-cafe] Style

2007-08-24 Thread Marc A. Ziegert

Marc A. Ziegert [EMAIL PROTECTED]

 tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
   where fives = iterate (*5) 1
 tm_improved_v1 n = sum . takeWhile (0) $ iterate (div `flip` 5) (div n 5)
 tm_fastestIMHO n = let m=div n 5 in if m5 then m else m+tm_fastestIMHO m


Henning Thielemann [EMAIL PROTECTED]

 tm4 = sum . takeWhile(0) . tail . iterate (flip div 5)


Bjorn Bringert [EMAIL PROTECTED]

 tm_silly n = length $ takeWhile (=='0') $ reverse $ show $ product [1..n]
 

Arie Groeneveld [EMAIL PROTECTED]

 tm = sum . takeWhile(0) . iterate f . f
where f = flip div 5
 tm1 n = sum . takeWhile(0) . map (div n . (5^)) $ [1..]
 tm2 n = sum . takeWhile(0) . map (div n) $ iterate ((*)5) 5
 tm3 = sum . takeWhile(0) . flip map (iterate ((*)5) 5) . div


signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Issue about use of WinHugs

2007-08-24 Thread Neil Mitchell
Hi

 I'm new to WinHugs, what's wrong with isUpper of my WinHugs?

Nothing. The book/tutorial you are going from is out of date. Before
using the isUpper/isLower functions you first have to type :load
Char:

Hugs :load Char
Hugs filter isUpper ABCDEfgh
ABCDE

The :load Char loads the Char module into scope, which provides the
isUpper function.

The haskell@ mailing list is mainly for announcements, so I've sent
this email to haskell-cafe@ - which is the right place for questions
like this.

Thanks

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


[Haskell-cafe] 2D game graphics library for Haskell?

2007-08-24 Thread peterv
I’m currently playing around with SOE to make some simple interactive math
exercises for students. This worked fine, although I could have done this
much faster using C# (which I know very well), but since I’m addicted to
Haskell now, I used the latter language ;) Furthermore, I hope that one day,
I will know enough Haskell to learn it to the students, because I feel that
functional programming should not be given in the last bachelor or master
years, since most software engineering students then know OO programming
extremely well and have a horrible time with FP (I currently did not meet
anyone in my sector of game development that liked FP, and many of those
people had a masters degree and some were PhDs)

 

Anyway, SOE is great for learning Haskell, but it lacks a couple of
fundamental functions to make it really attractive, like:

 

-Support for images

-Support for rendering to an “offscreen graphics surface” and
reading the pixels from that surface (for pixel-wise collision detection)

-Support for detecting non-ASCII key presses (cursor keys, etc)

-Support for joysticks

 

Concurrent Clean seems to have a nice 2D game library and PLT/DrScheme also
has nice support for basic 2D graphics, but somehow I feel Haskell is more
mature and more elegant. 

 

So before digging into “advanced” APIs (like GTK itself, which I know
nothing about, I’m a Win32 GDI/XNA/WPF expert), I should ask the question if
something similar exists? It has to be as simple as SOE.

 

Would it be possible to extend the GTK SOE with support for the features
mentioned above? Is this insanely difficult for someone like me who knows a
lot about Win32 but little Haskell?

 

Thanks,

Peter Verswyvelen

 


No virus found in this outgoing message.
Checked by AVG Free Edition. 
Version: 7.5.484 / Virus Database: 269.12.4/969 - Release Date: 23/08/2007
16:04
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Style

2007-08-24 Thread Arie Groeneveld

Thanks for all the instructive replies
and alternatives! Learned a bit more in
terms of feeling about style and improvement
of some of the functions: f.e. 'killing'
the 'where' in my number one choice.



Thanks

@@i


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


[Haskell-cafe] Re: newbie : multi-parameter type classes

2007-08-24 Thread Christian Maeder
Thomas Girod wrote:
 class (Eq n, Eq e) = Topo a n e where
 empty:: a

empty does not allow to infer the types n and e

 nodes:: a - [n]

also nodes leaves the type e undetermined

http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#functional-dependencies

Unfortunately
http://www.cse.ogi.edu/~mpj/pubs/fundeps.html
is broken.

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


[Haskell-cafe] Re: newbie : multi-parameter type classes

2007-08-24 Thread Christian Maeder
Thomas Girod wrote:
 Hi there.
 
 I'm trying to define a generic graph type here and don't understand on
 one error I get. Here I come.
 
 module Graph
  where
 
 class (Eq n, Eq e) = Topo a n e where
 empty:: a
 nodes:: a - [n]
 edges:: a - [e]

This does not work without functional dependencies. Try:

 class (Eq n, Eq e) = Topo a n e | a - n e where

HTH Christian

P.S. Integer comes in via defaulting (of 0 or 1)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Style

2007-08-24 Thread Arie Groeneveld
Henning Thielemann wrote:

 tm4 = sum . takeWhile(0) . tail . iterate (flip div 5)

FWIW: as a result of all this I learned to write this as:

tm41 = sum . takeWhile(0) . tail . iterate (`div` 5)



@@i



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


Re: [Haskell-cafe] Re: newbie : multi-parameter type classes

2007-08-24 Thread Matthew Brecknell
 Unfortunately
 http://www.cse.ogi.edu/~mpj/pubs/fundeps.html
 is broken.

http://web.cecs.pdx.edu/~mpj/pubs/fundeps.html

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


[Haskell-cafe] 2D game graphics library for Haskell?

2007-08-24 Thread Ben Lippmeier
 

Hi Peter, 

The OpenGL/GLUT bindings support all the things you would want, but it's a
bit too much pain for first year students. 

 

For the last couple of years at the ANU (Australian National University,
Canberra) we've been using a front end library that I wrote which is similar
to SOE/HGL but with support for images, animation, alpha blending and some
other things. I think the real trick is hiding enough of the OpenGL/GLUT
internals to make it suitable for first year students, while at the same
time exposing enough functionality so they don't feel constrained by what
they can do with the library. Usually we think of the project we want the
students to do, then supply most of the infrastructure via the library -
leaving the students to fill in the 'fun' stuff.

 

There is the added benefit that the OpenGL/GLUT bindings (and hence our
library also) compiles out of the box on both Linux and Windows. We use
linux machines at uni for the student labs, but students have been able to
take their code home and get it running on their home Windows PC's without
much difficulty.

 

You can get our library (with examples) from my homepage at
http://cs.anu.edu.au/people/Ben.Lippmeier/

 

I've also got a simple asteroids game which I wrote with an extended version
of it. There is a playable version, but unfortunately it's on my home
machine that is now packed in storage while I'm at MSR, Cambridge. I'm
getting back to Canberra late October so if you're still interested I can
dig it out and send you a copy then.

 

Cheers,

Ben.

 

 

 

From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of peterv
Sent: 24 August 2007 11:32
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] 2D game graphics library for Haskell?

 

I'm currently playing around with SOE to make some simple interactive math
exercises for students. This worked fine, although I could have done this
much faster using C# (which I know very well), but since I'm addicted to
Haskell now, I used the latter language ;) Furthermore, I hope that one day,
I will know enough Haskell to learn it to the students, because I feel that
functional programming should not be given in the last bachelor or master
years, since most software engineering students then know OO programming
extremely well and have a horrible time with FP (I currently did not meet
anyone in my sector of game development that liked FP, and many of those
people had a masters degree and some were PhDs)

 

Anyway, SOE is great for learning Haskell, but it lacks a couple of
fundamental functions to make it really attractive, like:

 

-  Support for images

-  Support for rendering to an offscreen graphics surface and
reading the pixels from that surface (for pixel-wise collision detection)

-  Support for detecting non-ASCII key presses (cursor keys, etc)

-  Support for joysticks

 

Concurrent Clean seems to have a nice 2D game library and PLT/DrScheme also
has nice support for basic 2D graphics, but somehow I feel Haskell is more
mature and more elegant. 

 

So before digging into advanced APIs (like GTK itself, which I know
nothing about, I'm a Win32 GDI/XNA/WPF expert), I should ask the question if
something similar exists? It has to be as simple as SOE.

 

Would it be possible to extend the GTK SOE with support for the features
mentioned above? Is this insanely difficult for someone like me who knows a
lot about Win32 but little Haskell?

 

Thanks,

Peter Verswyvelen

 

 

No virus found in this outgoing message.
Checked by AVG Free Edition.
Version: 7.5.484 / Virus Database: 269.12.4/969 - Release Date: 23/08/2007
16:04

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


Re: [Haskell-cafe] Style

2007-08-24 Thread sievers
Arie Groeneveld wrote:

 tm = sum . takeWhile(0) . iterate f . f
where f = flip div 5

 Which one is the most elegant one generally speaking?

I like that tm only uses div.

 My personal choice is 'tm'.
 I like 'tm3' (a revised version of tm2) in terms of
 pointlessness and not having a 'where', but I think
 it's a bit contrived because of the 'flip'.

You can make tm whereless by noticing that you use because
you use the function twice in  iterate f . f, which is because
you don't want the initial value that iterate gives.
You can instead use tail on iterate's result, and use a section
to avoid flip:

tm = sum . takeWhile (0) . tail . iterate (`div` 5)

(Hope that works, can't test now...)


All the best
Christian Sievers
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] IO inside CGI

2007-08-24 Thread Adrian Neumann
-BEGIN PGP SIGNED MESSAGE-
Hash: RIPEMD160

I'm toying around with web programming in Haskell. I'm trying to write a
script which GETs an id and returns a couple of random numbers.
Something like this:

cgiMain :: CGI CGIResult
cgiMain = do
inp - getInput id
let gen = parse inp
output $ take 10 (randoms gen)

parse :: Maybe String- StdGen
parse (Just x) = read x
parse Nothing = undefined

Now I'd like to get a new StdGen, in case no id was supplied to the script.

cgiMain :: CGI CGIResult
cgiMain = do
inp - getInput id
gen - parse inp
output $ take 10 (randoms gen)

parse :: Maybe String- IO StdGen
parse (Just x) = return $ read x
parse Nothing = getStdGen

Obviously this doesn't work because I'm trying to do IO inside CGI
(right?). Is there some incantation I can perform to make this possible?
Like

gen - arcaneMagic parse inp

As you probably have noticed I don't know very much about monads, all I
did until now was reading or writing some files.

Thanks in advance
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.4.7 (MingW32)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGzudU11V8mqIQMRsRA33RAJ9buZDHgz/eXi8Jw9OBwbTErDccRgCfbGrr
1WXiGHmxlTBe01E409yJyv8=
=XSDj
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: IO inside CGI

2007-08-24 Thread apfelmus

Adrian Neumann wrote:

Now I'd like to get a new StdGen, in case no id was supplied to the script.



parse :: Maybe String- IO StdGen
parse (Just x) = return $ read x
parse Nothing = getStdGen

Obviously this doesn't work because I'm trying to do IO inside CGI
(right?). Is there some incantation I can perform to make this possible?


Abracadabra, the incantation is

  liftIO :: IO a - CGI a

i.e.

  parse :: Maybe String- CGI StdGen
  parse (Just x) = return $ read x
  parse Nothing  = liftIO getStdGen


Regards,
apfelmus

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


Re: [Haskell-cafe] IO inside CGI

2007-08-24 Thread Chaddaï Fouché
2007/8/24, Adrian Neumann [EMAIL PROTECTED]:
 Obviously this doesn't work because I'm trying to do IO inside CGI
 (right?). Is there some incantation I can perform to make this possible?
 Like

 gen - arcaneMagic parse inp

As doing IO in the CGI Monad is a current need, it's an instance of
MonadIO and as such provide liftIO, so your arcaneMagic is called
liftIO :

cgiMain :: CGI CGIResult
cgiMain = do
   inp - getInput id
   gen - liftIO $ parse inp
   output $ take 10 (randoms gen)

parse :: Maybe String- IO StdGen
parse (Just x) = return $ read x
parse Nothing = getStdGen

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


[Haskell-cafe] RE: Re: Remember the future

2007-08-24 Thread Benjamin Franksen
Simon Peyton-Jones wrote:
 | It is unfortunate that the [ghc] manual does not give the translation
rules, or at
 | least the translation for the given example.
 
 Hmm.  OK.  I've improved the manual with a URL to the main paper
 http://citeseer.ist.psu.edu/erk02recursive.html
 which is highly readable. And I've given the translation for the example
as you suggest

Cool, thanks.

BTW, the Haskell' wiki says its adoption status is 'probably no' which I
find unfortunate. IMHO recursive do is a /very/ useful and practical
feature and the cons listed on
http://hackage.haskell.org/trac/haskell-prime/wiki/RecursiveDo don't weigh
enough against that. Ok, just my (relatively uninformed) 2 cents.

Cheers
Ben

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


[Haskell-cafe] Re: Remember the future

2007-08-24 Thread ChrisK
Benjamin Franksen wrote:
 Simon Peyton-Jones wrote:
 | It is unfortunate that the [ghc] manual does not give the translation
 rules, or at
 | least the translation for the given example.

 Hmm.  OK.  I've improved the manual with a URL to the main paper
 http://citeseer.ist.psu.edu/erk02recursive.html
 which is highly readable. And I've given the translation for the example
 as you suggest
 
 Cool, thanks.
 
 BTW, the Haskell' wiki says its adoption status is 'probably no' which I
 find unfortunate. IMHO recursive do is a /very/ useful and practical
 feature and the cons listed on
 http://hackage.haskell.org/trac/haskell-prime/wiki/RecursiveDo don't weigh
 enough against that. Ok, just my (relatively uninformed) 2 cents.
 
 Cheers
 Ben

I will assume that the current compilers will keep the current mdo desugaring.
 It is incredibly valuable, and I use it in two different monad stacks in the
regex-tdfa package I released.

It has been an implemented extension for quite several version of GHC, and with
the separate mdo keyword it does not interfere with other code.

Why have a lazy language with added monad do sugaring support and balk at
adding such a well tested and deployed way to use sugar for combining laziness
and monads?  Toy there g is an identity monadic version of f and h shows the
kind of logic I tend to intersperse in an mdo block:

 module Main where
 
 import Control.Monad.Fix
 import Control.Monad.Identity
 import Control.Monad.Writer
 
 f x = do
   let a = x*b
   b = x+1
   return a
 
 test_f = runIdentity (f 2) -- 6
 
 g x = mdo
   a - return (x*b)
   b - return (x+1)
   return a
 
 test_g = runIdentity (g 2) -- 6
 
 h x = mdo
   a - return (x*b)
   if even b then tell [('a',a)] else return ()
   b - return (x+1)
   tell [('b',b)]
   return a
 
 test_h1 = (runWriter (h 1)) -- (2,[('a',2),('b',2)])
 test_h2 = (runWriter (h 2)) -- (6,[('b',3)])

-- 
Chris

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


Re: [Haskell-cafe] Re: Graph reduction [Was: Where is StackOverflow on the Wiki?]

2007-08-24 Thread Andrew Coppin

Shiqi Cao wrote:

Check out this

http://www.cas.mcmaster.ca/~kahl/HOPS/ 
http://www.cas.mcmaster.ca/%7Ekahl/HOPS/




Heh. I was thinking about trying to build something *exactly like* this...

OOC, how the heck did they make it work through a document interface? 
Surely that's impossible?



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


[Haskell-cafe] Haskellnet could not find network-any dependency.

2007-08-24 Thread Edward Ing
Hi,
I am trying to install Haskellnet. But the configuration breaks on
dependency of network-any in GHC 6.6.

I thought network-any was part of Hierarchical libraries?

If not where do I get it?

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


Re: [Haskell-cafe] Help using CGIT

2007-08-24 Thread Rich Neswold
On 8/24/07, Bjorn Bringert [EMAIL PROTECTED] wrote:

 On Aug 23, 2007, at 3:34 , Rich Neswold wrote:

  Bingo! Method #3 works beautifully! I missed the using-lift-with-
  the-constructor permutation.
 
  Thanks for your help!

 I started writing a tutorial for Haskell web programming with the cgi
 package a while back, but haven't worked on it for a while, see
 http://www.haskell.org/haskellwiki/Practical_web_programming_in_Haskell
 I haven't added it to the list of tutorials yet, since it's still
 rather incomplete.

 The section on using CGIT is just a stub, perhaps you would like to
 contribute to it? See
 http://www.haskell.org/haskellwiki/
 Practical_web_programming_in_Haskell#Extending_the_CGI_monad_with_monad_
 transformers


Done. As I learn more about using CGIT, I'll try to remember to add more
content. Any suggestions to improve it are welcome!

-- 
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Style

2007-08-24 Thread Marc A. Ziegert
whops... i did check it, but
that was a copypaste mistake.

buggy:
 tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
   where fives = iterate (*5) 1

should be:
 tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
   where fives = iterate (*5) 5

- marc


Am Freitag, 24. August 2007 schrieben Sie:
 Hi Marc
 
 First off, thanks for your reply.
  tm_parallelizable_v1 = \n - sum . takeWhile (0) $ map (div n) fives
 where fives = iterate (*5) 1
 Did you check this one? IMHO I think it's producing the 'wrong' answer.
 
 *Main tm_parallelizable_v1 100
 124
 (0.00 secs, 0 bytes)
 
 *Main tm 100
 24
 (0.00 secs, 0 bytes)
 
 If comparing the result to the other variants is accepted as a sort
 of proof. ;-)
  
 But calculating the number of trailing zero's of n! is a matter of
 counting powers of five in the factorized n!: f.e.:
 
 10! = 1 2 3 2^2 5 2*3 7 2^3 3^2 2*5
 -- 5^2 -- picking up enough powers of 2 -- (2*5)^2 = 100
 
 So you will have to correct your 'fives' to f.e.
 
 fives = tail $ iterate (*5) 1
 
 
 
 Regards
 
 
 @@i
  
 
 




signature.asc
Description: This is a digitally signed message part.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe