[Haskell-cafe] Re: Web server continued

2007-12-31 Thread Joost Behrends
I forgot 2 things:
 
 The distinction between '=' and '==' is much like in C, although mixing
 them up is not so dangerous like in C. ':=' and '=' like in Wirth
 languages would be nicer.
 

Strangely nobody reacted on this. That a=a+1 is an infinite recursion here
(but _|_ obviously not completely out of scope) makes = totally different
in my eyes. And that outside monads variables normally have just one line,
where they are on the left side, makes another huge difference in the structure
of your code.

Then - more on wrapper libraries for SQL or HTML.

I consider interpolation useful with HTML, that is kind of other way around
than WASH. You write a page and embed your high-level in it. Not HTML should
bended to your high-level language. The so much mightier language should do the
service here. Then sides can possibly be upgraded by extern web designers.

With Python i realized an own way of embedding a (greatly reduced) subset of the
language into HTML - the project at sourceforge.net is named thrases.

And concerning SQL: I like the parts of the language - all capitalized - as
landmarks in my code, even in modified forms like:

 SELECT number, customer FROM  ++ currcols ++ 

Here i see from afar, what the code around this line does.

Happy New Year, Joost 


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


[Haskell-cafe] Re: Web server (Was: Basic question concerning data constructors)

2007-12-31 Thread Joost Behrends
Hi, 

 So how, prey tell, do you factor out an expression which includes
 p.../p?  It is not Haskell,
 Haskell has no power there.  Surely
 learning that mapping is easier than building your own (which will
 doubtlessly be worse (no
 offense, that's the first law of library use)).
 
 And since you are a Haskell beginner, learning a library will teach
 you not only the library, but
 loads about common idioms and Haskell programming in general.  As an
 example, it was only
 after using the Parsec library that I finally came to terms with
 monads; for whatever reason, I
 was incapable of grokking them studying only the standard built-ins.
 
 I dunno, it just seems odd to me to avoid extra learning when you're
 trying to learn the
 language in the first place.
 
 Luke
 
this is very debatable. Yesterday i read there should be no libraries at all
from anyone here. And i know from Python, that libraries can be bad - i rewrote
ftplib for my own use. I differentiate always between the language core and
its libraries. Pythons unicode is catastrophic - but the core language is 
very, very fine.

If there were a better STDLIB (and not many of them and Boost on top)
and no autoconf, i would stick to C++. Still the fastest language and 
very powerful with types, respective classes.

And i will embed Haskell into websides - thats the next step after
having ported the server. The least, what can be done here, and can be done
easily, is a kind of preprocessor. Perhaps i'll call it phaskelp 
(? - or phasp ?).

Happy New Year, Joost


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


[Haskell-cafe] Basic question concerning data constructors

2007-12-30 Thread Joost Behrends
Hello,

perhaps i will make a wishlist of topics not dealt in the tutorials. Here is 
something i miss in each of them: notes at the semantics of data constructors.

We read 

data Pair a b = Pair a b

in YetAnotherHaskellTutorial. And that is all ! If we omit data here, this 
would be a silly pleonasm. And no single word about this strange behavior of 
data in every tutorial i read.

A similar point: The tutorials teach, that = has a similar meaning than = in
mathematics. But there is a big difference: it is not reflexive. The 
the right side is the definition of the left. Thus x=y has still some kind of
temporality, which mathematics doesn't have. Wadler himself describes bunches
of lazily computed equations as dataflows somewhere.

Ok, so much on theory. Here a concrete question:

For adapting hws (one of the reasons for me to be here, not many languages have
a native web server) to Windows i must work on time. In System.Time i found

data ClockTime = TOD Integer Integer

2 questions arise here: Does this define TOD (which i do not find elsewhere)
together with ClockTime also ? And: Why is this not: 

data ClockTime Integer Integer = TOD Integer Integer ?

Is it just an abbreviation for the first? Or is there a connection to
ClockTime as an abstract data type (a notion, which would have a subtle
different meaning than in OOP - since instance is such different thing
here).

Thanks for your attention, Joost


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


[Haskell-cafe] ReRe: Basic question concerning data constructors

2007-12-30 Thread Joost Behrends
Thanks to both fast answers.

there remain problems with Jakes mail for me. This:

 When you define datatypes, you are essentially defining a type-level  
 constructors on the left hand side and (value-level) constructors on  
 the right hand side.

is very useful for me. data defines TWO constructors, ok. And if i want
construction on the type level, then the arguments must obviously be
type-valued, means parameters. From this i conclude, that 

data ClockTime Integer Integer = ...

would never make sense, whatever on the right size. The next isn't
understandable for me - i have not the slightest conception of dependently 
typed languages.

Then i arrive at
 
 . Now, let's say we had tried defining ClockTime with parameters as  
 you suggested.
 
   ClockTime' :: Integer - Integer - *
 
 Do you see the problem? In order to use the ClockTime type  
 constructor, we would have to use Integer values.

Cannot see any problem here - do we NOT want ClockTime to be initialized by two
Integers ? Or is this the main reason for introducing TOD - to be able to
 change it without having to make any changes to code using ClockTime ?
To repeat myself - am i right understanding, that this needs a differently named
data constuctor ?

(I cited abstract type from the library reference. Not 
important for me at the moment, what that means in Haskell.)

Thanks for your attention, Joost

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


[Haskell-cafe] Re: Web server (Was: Basic question concerning data constructors)

2007-12-30 Thread Joost Behrends
Thanks for that info:
 
 Several people have adapted and further developed HWS:
  
http://www.haskell.org/haskellwiki/Applications_and_libraries/Web_programming#Web_servers
 
   http://darcs.haskell.org/hws/
   http://www.informatik.uni-freiburg.de/~thiemann/WASH/ (WSP)
 
 There is also a mailing list dedicated to Haskell and Web development:
   http://www.haskell.org/mailman/listinfo/web-devel
 

I've already browsed through the docomentation of all that. Sorry, but i will 
not use WASH. I like things to be direct, to write  p { ... } or similar
things instead of p ... /p is worsening things for me.

Same with SQL.

To work competently with CSS or SQL you must learn that languages anyway.
(I still didn't master CSS2.1, but will have mastered it in the near future.
Haskell's pattern matching has helped me much to understand the selectors of CSS
- but problems with the natural flow of elements and positioning
are still there).

Using WASH (or HaskellDB) for me only means, that i must learn another 
interface on top of that. For databases i could imagine to do that for

1. Real database abstraction (which would require far more complete drivers, 
ODBC for example)
2. Mighty ORM abilities. 

With anything less, i do not want that extra learning. I consider the most
approaches as megalomanical, which
try to improve SQL. SQL is an ingenious achievement with its complete
avoidancs of iteration - it's working with sets - in an area, where performance
is everything. Still now it's a model for many things in language design -
i remember to have read something corresponding on www.haskell.org even (don't
remember the context).

For CSS (i try to do most things there, not in HTML) i see no use for that
extra learning at all.

Please do not feel offended. Sometimes i am too rash with hard words.

And concerning the web servers: I haven't seen any indication, that someone
has ported hws to Windows - as easy as that is. There is not even use of
unix domain sockets in hws, nothing unix-specific with IPC (or communication
among threads). It's just EpochTime and access permissions and only changes
in Utils.hs and Main.hs have to be made it seems (The other modules compile
on my system at least). If someone had done that, it would be in the core code 
of hws.

However it is kind of nasty for a Haskell beginner. The Windows API is
accessible via FFI, but nearly undocumented (and i am used to portability, do 
not want to study it earnestly. We have the module os in Python - i am missing
that in Haskell).

And time looks complicated in the standard lib. It was even an obstacle for
compiling HDBC (old-time had to be exposed - that is, what i thought at first,
but had to find out then, that cabal ignores exposition and hiding of modules 
:[[  ).

Cheers, Joost


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


[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

2007-12-22 Thread Joost Behrends
Stefan O'Rear stefanor at cox.net writes:


 If you can reproduce it on your machine (rm executable *.o *.hi
 between tests for maximum reliability), it's definitely a bug.
 
 http://hackage.haskell.org/trac/ghc/wiki/ReportABug
 
 Stefan

Yes, it was the same as before. Had i reboot meanwhile, because i was out for 
meal. 1.34 vs. 2.34 minutes are still the same times now, WITH deletion of the 
object files and the .exe between both compiles and runs.

What is happening here ? Does importing Data.Char shadow (in a hidden way) some
timeworn types or methods in the Prelude ? If so, ghc might be still faster
than it looks now.

Cheers, Joost




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


[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

2007-12-22 Thread Joost Behrends
Daniel Fischer daniel.is.fischer at web.de writes:

 I can't reproduce it, both run in 130s here (SuSE 8.2, 1200MHz Duron).
 However, it's running over 30 minutes now trying to factorise 2^88+1 without 
 any sign of approaching success, which suggests your code has a bug (the 
 factorization is [257,229153,119782433,43872038849], so even a naive approach 
 shouldn't take much longer than a minute).


I have found the problem: We must possibly work recursive on a found factor.
This was done in former versions, but got lost when isolating the function 
found. Here is a corrected version - complete again for reproducing easily
the strange behavior with Data.Char. It decomposes 2^88+1 in 13 seconds.


module Main
where

import IO
import System.Exit
--import Data.Char

main = do
hSetBuffering stdin LineBuffering
putStrLn Number to decompose ?
s - getLine
if s == [] then
exitWith ExitSuccess
else do
putStrLn (show$primefactors$read s)
main

data DivIter = DivIter {dividend :: Integer, 
divisor  :: Integer,
bound:: Integer, 
result   :: [Integer]}

intsqrt m = floor (sqrt $ fromInteger m)

primefactors :: Integer - [Integer]
primefactors n | n2   = []
   | even n= o2 ++ (primefactors o1)
   | otherwise = if z/=1 then result res ++[z] else result res
   where 
   res = divisions (DivIter {dividend = o1, 
 divisor = 3, 
 bound = intsqrt(o1),
 result = o2})
   z = dividend res  -- is 1 sometimes
   (o1,o2) = twosect (n,[])

twosect :: (Integer,[Integer]) - (Integer,[Integer])
twosect m |odd  (fst m) = m
  |even (fst m) = twosect (div (fst m) 2, snd m ++ [2])

found :: DivIter - DivIter
found x = x {dividend = xidiv,
bound = intsqrt(xidiv), 
   result = result x ++ [divisor x]}
where xidiv = (dividend x) `div` (divisor x)

d2 :: DivIter - DivIter
d2 x |dividend x `mod` divisor x  0  = x {divisor = divisor x + 2}
 |otherwise   = d2$found x
d4 :: DivIter - DivIter
d4 x |dividend x `mod` divisor x  0  = x {divisor = divisor x + 4}
 |otherwise   = d4$found x
d6 :: DivIter - DivIter
d6 x |dividend x `mod` divisor x  0  = x {divisor = divisor x + 6}
 |otherwise   = d6$found x

divisions :: DivIter - DivIter
divisions y |or[divisor y == 3, 
divisor y == 5]   = divisions (d2 y)
|divisor y = bound y = divisions (d6$d2$d6$d4$d2$d4$d2$d4 y)
|otherwise= y


And now it uses also 1.34 minutes for 2^61+1 without importing Data.Char.
Hmmm ...

Cheers, Joost

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


[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

2007-12-22 Thread Joost Behrends
Daniel Fischer daniel.is.fischer at web.de writes:
 
 Of course, one minute after I sent my previous mail, I receive this one :(
 However, one point, it might be faster to factor out all factors p in found 
 and only then compute the intsqrt, like
 
 found x = x{dividend = xstop, bound = intsqrt xstop, result = result x ++ 
 replicate k p}
 where
   p = divisor x
   (xstop,k) = go (dividend x) 0
   go n m
   | r == 0= go q (m+1)
   | otherwise = (n,m)
 where
   (q,r) = n `divMod` p

True - but be aware, that this will slightly slow down the computation for 
not multiple factors. And - as you recently noted - the really expensive
part are all the tried factors, which do not divide the queried number.

All this is just a first approach to the problem. When i talk of naively
programmed, then i want to say, that number theorists might have much better 
numerical orders marching through all primes plus some more odd numbers.
I didn't search for that on the net.

The last version was some kind of resign from tries like this:

firstPrimes = [3,5,7,11,13,17]
start = last firstPrimes
pac = product firstPrimes
slen = length lsumds

lsumds = drop 1 (fst$getSummands (singleton start, start)) where
getSummands :: (Seq Int, Int) - (Seq Int, Int)
getSummands r |snd r  bnd= getSummands ((fst r)|k, snd r + k) 
  |otherwise  = r
where
bnd = 2*pac + start
k = getNext (snd r)
getNext n |and [(n+2)`mod`x0 | x-firstPrimes] = 2 
  |otherwise= 2 + getNext (n+2)

smallmod :: Int - Int - Int
smallmod n m | nm = n | otherwise = 0

divstep :: (DivIter,Int) - (DivIter, Int)
divstep (x,n) | and [(fromInteger $ divisor x)start, ximod0] = 
  (x {divisor = divisor x + 2}, n)
  | (fromInteger$divisor x)  start = 
  (x {dividend = xidiv, 
  bound = intsqrt(xidiv), 
  result = result x ++ [divisor x]}, n) 
  | ximod0 = 
(x {divisor = divisor x + toInteger (index lsumds n)}, smallmod (n+1) slen)
  | otherwise = (x {dividend = xidiv, 
bound= intsqrt(xidiv), 
result   = result x ++ [divisor x]}, n) 
where 
(xidiv, ximod) = divMod (dividend x) (divisor x)

divisions :: (DivIter, Int) - (DivIter, Int)
divisions (y,n) | divisor y = bound y = divisions (divstep (y,n))
| otherwise= (y,0)

Here the additions to divisor are taken from the sequence lsmnds (List of
SuMaNDS) - the type Seq from Data.Sequence is faster with the function index 
than Data.List with !!. getSummands is a kind of reduced sieve of 
Eratosthenes. The main improvement is the longest line:

|ximod0 = (x {divisor = divisor x + toInteger (index lsumds n)}, 
   smallmod (n+1) slen)

I even considered converting lsmnds to ByteString and storing them - the
build of lsmnds for firstPrimes = [3,5,7,11,13,17,19,23,29] (which already
has some MB footprint) takes several minutes.  

But we have to track the number of iteration we are in. And that eats up
much more than the reduction of divisions for failing factors. The code works
(called slightly modificated by primefactors), but needs 5.41 minutes
for 2^61+1 :((. Also expensive might be the lookup in lsumds - the code gets
even slower with longer lists for firstPrimes.

divisions (d6$d2$d6$d4$d2$d4$d2$d4 y) is derived from

lsmnds [3,5] = [4,2,4,2,4,6,2,6].

For me the whole matter is closed for now - the 1.34 minutes are no bad result.
Amd anyway the code might represent a not too bad lower bound for efficiency of
decomposing algorithms. 

Auf Wiedersehen, Joost

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


[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

2007-12-22 Thread Joost Behrends
Sterling Clover s.clover at gmail.com writes:
 
 I'm curious if you get the same performance difference importing GHC.List
instead of Data.Char? I chased some dependencies, and Data.Char imports GHC.Arr,
which in turn imports GHC.List, which provides a bunch of fusion rules pragmas
that would probably optimize your (++) usage. If this is the case, not sure if
its a bug or not, but all this will have to be thought through as more stream
fusion is rolled out anyway, I suspect?
 
 
Yes - the same difference: 1.33 minutes vs. 2.30 now.

I was near at reporting this as a bug, but rejected that idea. What does bug
mean here ? I am really a rookie at Haskell - this working on primefactors
is nothing but an excercise (however i casually try number theoretic
problems and often missed a program like this). But - as it appears to me -
the dramatic advance in speed ghc has made recently is to a great extent
due to improved types and their methods. What i see at 
haskell.org/ghc/docs/latest/html/libraries looks like huge road works to me.

And then it is not a bug, if elder libraries as the Prelude perhaps are not
completely up to date.

Another problem is, that my program was not completely correct. But it didn't
crash and got most numbers decomposed correct. But the strange
behavior disappeared with a correct version. 

Perhaps the Prelude will get better now. 

Cheers, Joost



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


[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

2007-12-22 Thread Joost Behrends
Neil Mitchell ndmitchell at gmail.com writes:
 
 If it can be reproduced on anyones machine, it is a bug. If you can
 bundle up two programs which don't read from stdin (i.e. no getLine
 calls) or the standard arguments (i.e. getArgs) which differ only by
 the Data.Char import, and have massive speed difiference, then report
 a bug.
 
 You should probably also give your GHC versions and platforms etc.

Thanks for your attention too !

Now i tried a version without input (just computing the primefactors of the
constant 2^61+1, what it did correctly in spite of its bugginess). And it
didn't have the Data.Char bug (and Data.List bug) too.

As my original code hasn't on Linux also it seems.

Thus it  happens only in an exotic configuration. Windows will stay exotic
in the Haskell community. Before should noone
has reproduced it at least on Windows (XPpro SP2 is my version), i will do 
nothing more.

The hardware is Intel Celeron 2.2GHZ, 512 MB Ram. ghc 6.8.1 lives on
D:\\Programme (not on the system drive C:, which poses problems to Cabal, 
told aside). I just made the standard installation (do not remember, whether
by unzipping alone or there was an MSI) not touching anything, of course. 
I was happy about no autoconf (which i see in the category of desasters like
EMM386 for MS-DOS).

But something is strange: ghci doesn't accept
qualified imports. It produces a parse error. That seems a bug to me, because
my ghci accepts import (any module) nevertheless. But i see it as a minor
bug - the compiler is much more important.

Happy days, Joost

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


[Haskell-cafe] Re: Importing Data.Char speeds up ghc around 70%

2007-12-22 Thread Joost Behrends
Hi again, Daniel

cannot sleep tonight - perhaps from the feeling to loose too much time with
these things.

Yes - it's the wheel. And a dlist made from [3,5,7,11,13,17] was optimal in some
of my experiments too.

You will probably know it - but perhaps there are third-party readers:
A last try to improve the final version was to replace Integer by Int64
(importing Prelude qualified). There was no difference ! That is good news
and bad - the good news (and that's much more important), that Integer is
absoulutely cleanly implemented. 

However, if this is so, i have little sympathy for
being forced to use fromInteger and toInteger - for this special case i would
prefer automatic coercion. And - sorry - cannot do other than seeing anything
else as ill-advised dogmatism. But perhaps i am spoiled from Python :).

I did this, because for secure decision about divisibility the program 
isn't useful beyond that.

Thanks for that entry point: I took google Rabin-Miller in a comment of this 
last version.

Happy days, Joost  

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


[Haskell-cafe] Re: MonadFix

2007-12-21 Thread Joost Behrends
@apfelmus,

please read my code. I introduced DivIter to separate divstep from divisions.
But it stores intsqrt dividend also. Thus the sqrt is only recomputed, when a
new factor is found.

Concerning primes': With the sieve of Eratosthenes we cannot make a lazy list,
we need the whole list at any point of computation. And beyond the end we fall
back to x - x+2.

This is the difference to the list of summands i proposed. And we have the
arbitrary choice of [2,4], [2,4,2,4,2,4,2,6,2,6] or any longer.

Concerning State: There is useful instruction by Ryan Ingram too here. I will
study that and yours. Thank you !

Cheers, Joost







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


[Haskell-cafe] Re: MonadFix

2007-12-21 Thread Joost Behrends
@apfelmus,

please read my code. I introduced DivIter to separate divstep from divisions.
But it stores intsqrt dividend also. Thus the sqrt is only recomputed, when a
new factor is found.

Concerning primes': With the sieve of Eratosthenes we cannot make a lazy list,
we need the whole list at any point of computation. And beyond the end we fall
back to x - x+2.

This is the difference to the list of summands i proposed. And we have the
arbitrary choice of [2,4], [2,4,2,4,2,4,2,6,2,6] or any longer.

Concerning State: There is useful instruction by Ryan Ingram too here. I will
study that and yours. Thank you !

Cheers, Joost







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


[Haskell-cafe] Re: MonadFix

2007-12-21 Thread Joost Behrends
apfelmus apfelmus at quantentunnel.de writes:

 Huh?  p  intsqrt n  is evaluated just as often as  p*p  n , with 
 changing  n  . Why would that be less expensive? Btw, the code above 
 test for  r==0  first, which means that the following  p*p  n  is 
 tested exactly once for every prime candidate  p .

No. One point in the introduction of DivIter is, that intsqrt dividend is stored
there and only recomputed, when a new factor is found.

And concerning my cycled lists of summands as [2,4] or [2,4,2,4,2,4,2,6,2,6]:

There simply is no function easily yielding primes for your list primes'. 
If we use the sieve of Eratosthenes, we must have the whole list 
of found primes up to a certain point in memory for proceeding 
beyond that certain point. We cannot gain anything by lazy evaluation. 
Not with the sieve of Eratosthenes - and there is no other reliable mechanism.

What is more - if we have a list of primes, possibly up to 1,000,000 - what
shall we do for efficiently yielding divisors beyond 1,000,000 ? We would have
to fall back to x - x+2.

Thus an easily computable function stepping through all primes can only be
a function, which yields primes plus some more odd numbers. This is, what i
tried. Alternating addition of 2 and 4 to the current divisor can be continued 
beyond any bound. And i am not forced to use any of the longer list of
summands - indeed, which of these lists to choose should be adapted to the
size of the number to decompose.

Concerning the State monad:

Yes, i was wrong here completely. Ryan Ingram gave detailed instructions why.
And Albert Y.C. Lai pointed out, that normal recursion for division works
tail recursive too. It didn't on my computer - perhaps i misconfigured
ghci (where i tried it). Let us close discussion of this point.

Cheers, Joost

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


[Haskell-cafe] Re: MonadFix

2007-12-20 Thread Joost Behrends
Albert Y. C. Lai trebla at vex.net writes:

 Theoretically the recursions in
 
  oddFactors k n | otherwise = oddFactors (k+2) n
 
 and
 
 (*) divisions y |divisor y = bound y = divisions (divstep y)
 
 do not cost stack space. They are tail recursions too!
 
 In general similar tail recursions do not cost stack space. Some 
 programs using them use a lot of stack space, but that is because of 
 non-strictness, not because of tail recursion itself. And such 
 non-strictness is absent here due to the way the parameters have to be 
 evaluated for all sorts of decisions before further recursive calls.


Thanks for all that benchwork (and especially your exponent 61). I must admit,
that i ran the (*) version in ghci only (not having compiled it 
to a standalone version). Maybe ghci is configured wrongly on my system. 
As i remember, i tried (*) twice, coming near to memory exhaustion 
and not awaiting the result. I would really like a non-monadic version. 

What is interesting also is how near your 19 minutes came to my 17 
(Windows XP, 2.2GHZ, 512MB). And the comparations to Daniels code 
seem to imply, that my named fields in DivIter are 
not very expensive, if at all.

Is there documentation of tail recursion anywhere ? I searched
(googling with site:www.haskell.org) and didn't find anything else 
than entries in mailing lists.

Cheers, Joost




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


[Haskell-cafe] Re: MonadFix

2007-12-20 Thread Joost Behrends
apfelmus apfelmus at quantentunnel.de writes:

 How about separating the candidate prime numbers from the recursion
 
factorize :: Integer - [Integer]
factorize = f primes'
   where
   primes' = 2:[3,5..]
   f (p:ps) n
  | r == 0= p : f (p:ps) q
  | p*p  n   = [n]
  | otherwise = f ps n
  where
  (q,r) = n `divMod` p

Providing effectively primes' for that is simply impossible 
(besides: p  intsqrt n must stay, otherwise you have
the expensive p*p at every step) talking about really big numbers 
as i did in my post. There are no fast generators iterating just
through the primes firstly, and these lists get much too big also 
(for 2^120 you cannot even begin to use a list of the primes 
up to 2^(any appropriate x) ).

What can be done is to iterate through odd numbers meeting as many primes 
as possible. We could do this:

iterdivisors x | x == 0 = 3
   | x == 1 = 5
   | otherwise x = iterdivisors (x-1) + ((cycle [2,4]) !! x)

This gives 7,11,13,17,19,23,25,29,31,35,37,41,43,47,49,53,55,59,61,63,67 ...

i.e. exactly all primes and odds with greater primefactors as 3.
We can improve that cycle avoiding the multiples of 5:

 ... | otherwise x = iterdivisors (x-1) + ((cycle [2,4,2,4,2,4,6,2,6] !! x)

and we can do better by avoiding the multiples of 7 and so on 
(the length of these lists grows fast - it gets multiplied 
by every new avoided prime -, but we could provide that lists 
programmatically). And we must be sure, that cycle
doesn't eat up memory for each new pass through the list. 
And we should use a more efficient representaion 
for the list of summands than a list.

This is the first front.

But the title of my post and much more interesting topic 
for learning Haskell is, how to avoid memory exhaustion by recursion. 
THIS was my intention and the reason why i erroneously brought MonadFix 
into the game. The recursion i described as follows

 divisions = do
y - get
if divisor y = bound y then do
put ( divstep y )
divisions
else return y

makes a DESTRUCTIVE UPDATE of the DivIters (by put) and this kind of recursion
seems not to remember itself (as i have understood, that is achieved by 
tail recursion). I just didn't like making DivIters to States. 
It's kind of lying code.

However it worked and improved performance by a factor around 10 
(or oo - perhaps a normal recursion exhausts 512MB memory for 2^120+1, 
as it will do for much smaller Integers, if they are prime) 
not to talk about footprint. Compiled for running standalone, 
it took 17 minutes, an equivalent python script 2 hours.
This factor near 7 is not fully satisfactory. 

There are more workarounds beside the State monad for having 
destructive updates with Haskell. There are IORefs, there are updatable arrays 
and more. THAT is my question: Is this (only basically) the most efficient way
to get them here ? 

Or is there still a way of getting a tail recursive Haskell function 
for iterating through the DivIters (outside any monads) ?? 
I would not get stroke dead by surprise if yes, but i couldn't find any.

Cheers, Joost

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


[Haskell-cafe] MonadFix

2007-12-18 Thread Joost Behrends
Hi,

since about three weeks i am learning Haskell now. One of my first excercises is
to decompose an Integer into its primefactors. I already posted discussion on
the solution to the problem 35 in 99 excercises.

My simple algorithm uses a datatype DivIter of 4 named fields together with the
core iteration 

divstep :: DivIter - DivIter
divstep x | divisor x  bound x = x
  | ximod  0= x { divisor = (divisor x) +2 }
  | otherwise=  x {dividend=xidiv, 
   bound=intsqrt(xidiv), 
   result = result x ++ [divisor x] } 
where
(xidiv, ximod) = divMod (dividend x) (divisor x)

(dividend x is already odd, when this is called).

The problem to solve for really large Integers is how to call divstep iterated
without not accumulating billions of stack frames. Here is one possibility:

divisions = do
y - get
if divisor y = bound y then do
put ( divstep y )
divisions
else 
return y

(this for a version of divstep without the first guard) called from

res = execState divisions (DivIter { dividend = o1, 
 divisor = 3, 
 bound = intsqrt(o1),
 result = o2 })

( where o1 the odd part of the number to decompose, o2 a list of its
contained twos). This computes the primefactors of 2^120+1 in 17 minutes after
all. But i cannot help feeling that this is an abuse of the State monad. The
MonadFix has a functionfix (a - a) - a   and i added the first guard in
divstep above for making this a fixpoint problem.

For me the signature looks, as if using fix doesn't afford to create explicitely
a variable of a MonadFix instance and a simple twoliner for divisions could do
the job. What i do not understand at all from the documentation of fix is:

   fix f is the least fixed point of the function f, i.e. the least defined x
such that f x = x.

What does least mean here ? There is nothing said about x being a variable of
an instance of Ord. And why fix has not the type a - (a - a) - a, means: How
can i provide a starting point of the iteration x == f x == f (f x) == ...?  



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


[Haskell-cafe] Re: New to Haskell: The End

2007-12-18 Thread Joost Behrends
Henning Thielemann lemming at henning-thielemann.de writes:

  - it is lazy with class
  - it is strongly typed
  - it has automatic memory management
  - it has a standard library
  - it has a compiler
  - it is available on several platforms
  - it has a community
  - it is free

There MUST be at least two adjectives added:

it has a FAST compiler (compare to MzScheme for example)
it is strongly and PARAMETRICALLY typed

And perhaps 

it has MONADS 

I am learning Haskell 3 weeks now and have the common difficulties to understand
them, but at the first sight this seems an extremely flexible and nevertheless
clean solution to the problem. And it doesn't stop at monads, there are comonads
and arrows too. And all this very actively and countiuously revised and
developed further.





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


[Haskell-cafe] Re: MonadFix

2007-12-18 Thread Joost Behrends
Daniel Fischer daniel.is.fischer at web.de writes:

 
 Am Dienstag, 18. Dezember 2007 17:26 schrieb Joost Behrends:
  Hi,
 
  since about three weeks i am learning Haskell now. One of my first
  excercises is to decompose an Integer into its primefactors. I already
  posted discussion on the solution to the problem 35 in 99 excercises.
 
  My simple algorithm uses a datatype DivIter of 4 named fields together with
  the core iteration
 
 But a simple recursion that returns the list of primefactors lazily would 
 also 
 solve the stack frame problem, wouldn't it?
 sort of
 factor 0 = error 0 has no factorisation
 factor 1 = []
 factor n
   | n  0 = (-1):factor (-n)
   | even n= 2:factor (n `div` 2)
   | otherwise = oddFactors 3 n
 
 oddFactors k n
   | k*k  n   = [n]
   | r == 0= k:oddFactors k q
   | otherwise = oddFactors (k+2) n
 where
   (q,r) = n `divMod` k
 
 you can then start consuming the prime factors as they come, before the 
 factorisation is complete.
 
Hi and thanks for your answers,

@Daniel: no, this doesn't solve the stack problem. These are the primefactors of
2^120+1: [97,257,673,394783681,4278255361,46908728641]. 

oddFactors k n | otherwise = oddFactors (k+2) n

could eventually push 394783681-673 function calls onto the stack before finding
the factor 394783681. And indeed a recursive version of divisions trying to
compute this ran more than two hours on my machine, before i stopped it (this is
the time a python script needs for the computation). And there were peaks of
memory use  300 MB ! While the version with the State monad seems to 
work tail recursive - it has an absolutely constant memory use, slightly
different per run, i watched 2044k and 2056k. And it takes around 17 minutes on
my machine getting the result.

Thus it's vital here, how the recursion is done. Because of that i separated
divisions and divstep - for experimenting with divisions. If a factor is done,
it should leave as little traces as possible on the machine.

Both of your instructions for fix are well readable - thanks again. I'll spend
some time studying them, but it seems, fix doesn't fix the problem.


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