[Haskell-cafe] Re: functional graphs

2008-01-21 Thread Mirko Rahn
..5] (\ x y - mod (x+y) 4) [(0,4,0,0),(4,5,1,1),(5,3,0,1),(3,1,0,1),(1,3,0,1),(3,2,1,2),(2,3,1,3),(3,5,0,3),(5,4,1,4),(4,0,0,4)] -} Have fun! /BR, Mirko Rahn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo

[Haskell-cafe] Re: Optimizing cellular automata evaluation (round 2)

2007-12-03 Thread Mirko Rahn
quite complex, hard to follow and hard to debug implementation. As always, I prefer to write most code in Haskell, quick, easy, nice, reasonable fast, ... If speed matters, I switch to some lower level language, as you did staying inside Haskell. /BR, Mirko Rahn

[Haskell-cafe] Re: New slogan for haskell.org

2007-11-30 Thread Mirko Rahn
that a Haskell program that verifies these values will depend on an external intset implementation. Or uses another data structure, for example some Set_of_Intervals... /BR, Mirko Rahn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

[Haskell-cafe] Re: New slogan for haskell.org

2007-11-29 Thread Mirko Rahn
to calculate a_{23448481} = 594261577728 and a_{2500} = 192365946 in 50s and ~1GB memory usage. /BR, Mirko Rahn ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: map/reduce example

2007-11-27 Thread Mirko Rahn
for message passing environments with the capability to send a message to a specific receiver. I'm quite not sure how to adopt it to the channel-based environment (except via simulating the message passing environment). /BR, Mirko Rahn ___ Haskell-Cafe

[Haskell-cafe] Re: About Fibonacci again...

2007-11-08 Thread Mirko Rahn
The Rabbit Sequence: 1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,1,0,... This nasty acquaintance of mine asked the students to write down a simple procedure which generates the sequence after the infinite number of units of time. Of course, any finite prefix of it. In

Re: [Haskell-cafe] Style

2007-08-24 Thread Mirko Rahn
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

Re: [Haskell] Ref class?

2007-08-16 Thread Mirko Rahn
does anyone know where there's a class that abstracts over IORefs? it includes newRef, readRef, and writeRef. i've seen it but can't remember where. - conal John Hughes, Functional Pearl: Global Variables in Haskell. /BR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http

Re: [Haskell-cafe] Re: monad subexpressions

2007-08-03 Thread Mirko Rahn
, where others need some help... /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: monad subexpressions

2007-08-03 Thread Mirko Rahn
memcpy() I like to hear that you would reject it either. /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: monad subexpressions

2007-08-03 Thread Mirko Rahn
rewriting it in Haskell (of any size) is a good idea to actually understand the code. Please, could you do it. /BR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-22 Thread Mirko Rahn
documentation states it very clearly. /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] Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-19 Thread Mirko Rahn
diff_eq_0 :: Eq a = [a] - [a] - Bool diff_eq_0 = diff (\ u v - null u null v) (const . const $ False) /BR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

Re: [Haskell-cafe] Time consumption nub

2007-07-18 Thread Mirko Rahn
lists, btw. /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] Construct all possible trees

2007-06-14 Thread Mirko Rahn
). As a consequence my version is faster and eats less memory. /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

Re: [Haskell-cafe] Re: Construct all possible trees

2007-06-14 Thread Mirko Rahn
) - [ Branch a b | a - the_trees l, b - the_trees r ] nonempty_splits (x:y:ys) = ([x],y:ys) : [ (x:l,r) | (l,r) - nonempty_splits (y:ys) ] nonempty_splits _= [] /BR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: [Haskell-cafe] Construct all possible trees

2007-06-13 Thread Mirko Rahn
- insert x part] all_trees [] = [] all_trees (x:xs) = let this = Leaf x more = all_trees xs in this : more ++ concatMap (insert this) more /BR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: [Haskell-cafe] Re: Construct all possible trees

2007-06-13 Thread Mirko Rahn
(Leaf 4) (Leaf 5))) So please, what's going on here? -- -- 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: readArray is faster than unsafeRead

2007-05-30 Thread Mirko Rahn
to exploit the recursive structure and some invariants of Gauss' algorithm in a direct way. BR, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org

Re: readArray is faster than unsafeRead

2007-05-29 Thread Mirko Rahn
and IO stuff... BR, (*) Try: newStdGen = \ g - flip mapM_ [gaussElimSafe,gaussElimUnsafe] $ \ f - makeMatrix g = \ m - printMatrix m f m printMatrix m -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- import Control.Monad (mplus,liftM) type Matrix

Re: [Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread Mirko Rahn
$ unlines . filter (ubuntu `super`) . lines 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: Slower with ByteStrings?

2007-05-29 Thread Mirko Rahn
Map.updateLookupWithKey ins y m of (Nothing,_ ) - mzero (_ ,m') - return m' in not . null . foldM upd mx Thanks for your time, BR, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: [Haskell-cafe] how can I select all the 3-element-combination out of a list efficiently

2007-05-21 Thread Mirko Rahn
sorting) ...but is exponentially slower than necessary, and fails on infinite lists. Try this one: sublistsN 0 _ = [[]] sublistsN n (x:xs) = map (x:) (sublistsN (n-1) xs) ++ sublistsN n xs sublistsN _ _ = [] triples = sublistsN 3 BR, -- -- Mirko Rahn -- Tel +49-721 608 7504

Re: [Haskell-cafe] how can I select all the 3-element-combination out of a list efficiently

2007-05-21 Thread Mirko Rahn
! Correct (and more natural): nOf 0 _ = [[]] nOf n (x:xs) = map (x:) (nOf (n-1) xs) ++ nOf n xs nOf _ [] = [] BR, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] How Albus Dumbledore would sell Haskell

2007-04-20 Thread Mirko Rahn
: This statement contradicts your easyness claim!? Add 2: In contrast, the Haskell solution does'nt uses advanced Haskell features (whatever this might be), it consists of 6 lines of plain Haskell 98 only. Regards, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: [Haskell-cafe] How Albus Dumbledore would sell Haskell

2007-04-19 Thread Mirko Rahn
this in your favorite language! Regards, -- -- 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] Algorithms

2007-03-19 Thread Mirko Rahn
A. understand the problem B. decompose or reduce it into subproblems C. solve the subproblems D. compose a solution from the sub-solutions -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell-Cafe mailing

Re: [Haskell-cafe] FFI basics

2007-02-16 Thread Mirko Rahn
constructed function. Regards, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- module Main where import System.Posix.DynamicLinker as DL import System.Process ( runInteractiveProcess , waitForProcess ) import Foreign.C ( CString , withCString ) import Foreign ( FunPtr

Re: Indentation of If-Then-Else

2006-10-25 Thread Mirko Rahn
-l 355 find . -name '*.hs' | xargs grep -v ^-- | grep -v ^$ | wc -l 28432 find . -name '*.hs' | xargs grep ' then ' | grep -v ':--' | wc -l 145 find . -name '*.hs' | xargs grep ' case ' | grep -v ':--' | wc -l 203 Regards, MR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de

Problem with lexically scoped type variables.

2006-10-02 Thread Mirko Rahn
relax the rules for lexically scoped type variables a bit? Regards, Mirko Rahn -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http

Re: Problem with lexically scoped type variables.

2006-10-02 Thread Mirko Rahn
the problem. So maybe one could 'quick hack' it into ghc!? Regards, MR -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org

Re: Problem with lexically scoped type variables.

2006-10-02 Thread Mirko Rahn
. But what works is to give some more detailed hints to the type system: t1S = trav f [1..10] (1,52) :: ST s (STRef s (Set Int)) t2S = trav f [1..10] (1,52) :: ST s (STUArray s Int Bool) t1 = runST ( t1S = seen ) t2 = runST ( t2S = seen ) This compiles (and works). Thank's for advice, MR -- -- Mirko

Re: [Haskell-cafe] Combinations

2006-06-06 Thread Mirko Rahn
) = [ x:y | x - xs, y - combinations xss ] BTW, I think 'cross_many' would be a better name. -- -- 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

Re: [Haskell] timing/timeout (how to express that in Haskell)

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

Re: [Haskell] timing/timeout (how to express that in Haskell)

2006-05-12 Thread Mirko Rahn
print expensive ) ( print cheap ) expensive cheap Uhhh, something's wrong here, *both* functions are executed... -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell mailing list Haskell@haskell.org http

Re: [Haskell-cafe] GetOpt

2006-05-02 Thread Mirko Rahn
-type technique first reads all options and then post-processes the complete set. Here the order of options on the commandline has no impact on the final result. Regards, Mirko Rahn -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Mirko Rahn
! Best regards, Mirko Rahn -- -- 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

[Haskell-cafe] List of instantiated types

2006-03-30 Thread Mirko Rahn
/haskell-cafe/2006-March/014947.html -- -- 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] Silly question on interactive import

2005-12-15 Thread Mirko Rahn
:m + Char :l parse would work, but loading destroys the access to the module Char. (:add as well). I remember that accessing functions from Char in a qualified matter should still be possible. / -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: GHC-6.4.1 much slower than GHC-6.4

2005-10-28 Thread Mirko Rahn
and 10123468 entries in 6.4.1-version, also about factor 4. I guess the 6.4.1-version does more work, although I don't know why... Mirko -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Glasgow-haskell-bugs mailing

GHC-6.4.1 much slower than GHC-6.4

2005-10-27 Thread Mirko Rahn
; done Regards, Mirko P.S.: I run a debian-box with i686 GNU/Linux 2.6.11.11 and a dualcore P4 3.2 GHz. -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Glasgow-haskell-users mailing list Glasgow-haskell-users

Re: [Haskell] best way to do generic programming?

2005-07-01 Thread Mirko Rahn
to implement functions that are extensible with new type-specific cases. Have fun, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman

Re: explicit signatures and default for integer literals

2005-05-31 Thread Mirko Rahn
where import A instance New [(a,Double)] (Map a Int) where ... When compiling A ghc cannot be sure, that there is no such instance, since it could be defined elsewhere. regards, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: explicit signatures and default for integer literals

2005-05-30 Thread Mirko Rahn
a Int g xs = new $ zip xs [0..] Why is ghc unable the determine the type of the Literal 0 in the definition of g? The definition of f works fine instead. Regards, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: explicit signatures and default for integer literals

2005-05-30 Thread Mirko Rahn
: Since somewhere an instance e.g. New [(a,Double)] (Map a Int) could be defined, leading to problems when threating 0 as (0::Int). Thanks to private communication, Cheers, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn

Re: [Haskell] rekursive array problem

2005-05-02 Thread Mirko Rahn
) have fun, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ --- ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell