[Haskell-cafe] Different semantics in identical do statement?

2009-10-09 Thread staafmeister


In my program

do
  x - do
blah - someFunc
return blah
  return $ Constructor x

behaves differently from
do
  blah - someFunc
  return $ Constructor blah

where the dots are identical. I would think that these programs should
behave identically, by the monad laws.
The result of my program is that the second gives correct behaviour, while
the first loops forever.

Greetings,
Gerben
-- 
View this message in context: 
http://www.nabble.com/Different-semantics-in-%22identical%22-do-statement--tp25828319p25828319.html
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] Different semantics in identical do statement?

2009-10-09 Thread staafmeister



Ross Mellgren wrote:
 
 In what Monad?
 
 

Parsec Monad

-- 
View this message in context: 
http://www.nabble.com/Different-semantics-in-%22identical%22-do-statement--tp25828319p25828521.html
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] Different semantics in identical do statement?

2009-10-09 Thread staafmeister



Daniel Peebles wrote:
 
 I vaguely remember on IRC someone pointing out that the Parsec monad
 broke one of the laws. I think return _|_  x === _|_ which could be
 causing your problem. I may be wrong though.
 
 

This could very well be it. I use lazy eval to construct a function that
returns
its own argument (that is you supply the return value of the func as its
arg).

-- 
View this message in context: 
http://www.nabble.com/Different-semantics-in-%22identical%22-do-statement--tp25828319p25828612.html
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] Different semantics in identical do statement?

2009-10-09 Thread staafmeister



Daniel Peebles wrote:
 
 I vaguely remember on IRC someone pointing out that the Parsec monad
 broke one of the laws. I think return _|_  x === _|_ which could be
 causing your problem. I may be wrong though.
 
 

Confirmed, working in the parsec monad

Prelude Text.Parsec runP (do {x - return undefined; return 10}) ()  
*** Exception: Prelude.undefined

In the IO Monad
Prelude Text.Parsec do {x - return undefined; return 10}
10

Should be fixed.

-- 
View this message in context: 
http://www.nabble.com/Different-semantics-in-%22identical%22-do-statement--tp25828319p25829017.html
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] line intersection code

2009-09-21 Thread staafmeister


Hi,

I wrote a O(n log n) line segment intersection code. Couple of questions

1) I did not find such a library on hackage (at least google gave no
results:)),
and I notice a lot of people submit packages. Would there be any interest 
to submit this code (would give incentive to make the code cleaner)

2) In the algo I needed a balanced binary tree, but with a compare function
that changes with each iteration. Is there a balanced binary tree available
that give more freedom in specifying the compare function. Data.Set does
not have this option (I think). Using unsafePerformIO to change the compare
function seemed a little bit ugly.


-- 
View this message in context: 
http://www.nabble.com/line-intersection-code-tp25530313p25530313.html
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] Why the stack overflow?

2009-09-19 Thread staafmeister


Hi haskell-cafe,

Why does rlist 10 [] gives stack overflow in ghci?

rlist 0 l = return l
rlist n l = do {x - randomRIO (1,maxBound::Int); let nl = x:l in nl `seq`
rlist (n-1) nl}

I first uses replicateM then foldM and finally an explicit function. But
they give all stack overflow
I don't know why 10 is not absurd and it is tail recursive. Or is it
not, due to the monad structure?

greetings
Gerben

-- 
View this message in context: 
http://www.nabble.com/Why-the-stack-overflow--tp25520431p25520431.html
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] memoization

2009-09-11 Thread staafmeister


Hi,

Investigating memoization inspired by replies from this thread. I
encountered something strange in the behavior of ghci. Small chance it's a
bug, it probably is a feature, but I certainly don't understand it :)

The interpreter session went as follows

GHCi, version 6.10.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Prelude :load test_bug.hs
[1 of 1] Compiling Main ( test_bug.hs, interpreted )
Ok, modules loaded: Main.
*Main let s1 = memo2 solve2
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package containers-0.2.0.1 ... linking ... done.
Loading package filepath-1.1.0.2 ... linking ... done.
Loading package old-locale-1.0.0.1 ... linking ... done.
Loading package old-time-1.0.0.2 ... linking ... done.
Loading package unix-2.3.2.0 ... linking ... done.
Loading package directory-1.0.0.3 ... linking ... done.
Loading package process-1.0.1.1 ... linking ... done.
Loading package random-1.0.0.1 ... linking ... done.
Loading package haskell98 ... linking ... done.
*Main :type s1
s1 :: [()] - [()] - ModP
*Main let s2 a b = memo2 solve2 a b
*Main :type s2
s2 :: (Eq t) = [t] - [t] - ModP

Here memo2 is a function that works like a combinator to obtain a memoized
recursive function. However the type of the function depends on how I define
it. In point-free style it gets the wrong
type, however if I define (s2) with explicit arguments the type is correct?
Do you know what happens here? I would expect the types to be the same.

Another question is: I use now makeStableName for equality but using this
function memoization does not work and it still takes a long (exponential?)
time to go through the codejam testcases. The memoization using data.map
works flawless.

Greetings,
Gerben

ps.

The content of test_bug.hs is

import Data.IORef
import System.IO.Unsafe
import Control.Exception
import qualified Data.Map as M
import Text.Printf
import qualified Data.HashTable as H
import System.Mem.StableName
import Data.Ratio
import Array

memo f = unsafePerformIO $ do
  cache - H.new (==) (H.hashInt . hashStableName)
  let cacheFunc = \x - unsafePerformIO $ do stable - makeStableName x
 lup - H.lookup cache stable
 case lup of
   Just y - return y
   Nothing - do let res = f
cacheFunc x
 H.insert cache
stable res
 return res
  return cacheFunc

memo2 f = curry $ memo (\g (x,y) - f (curry g) x y)

newtype ModP = ModP Integer deriving Eq

p=10007

instance Show ModP where
  show (ModP x) = printf %d x

instance Num ModP where
  ModP x + ModP y = ModP ((x + y) `mod` p)
  fromInteger x = ModP (x `mod` p)
  ModP x * ModP y = ModP ((x * y) `mod` p)
  abs = undefined
  signum = undefined

solve2 f _ [] = 1::ModP
solve2 f [] _ = 0::ModP
solve2 f (hs:ts) t@(ht:tt) | hs==ht = f ts tt + f ts t
   | otherwise = f ts t

go (run, line) = Case #++show run++: ++show ((memo2 solve2) line
welcome to code jam)

main = interact $ unlines . map go . zip [1..] . tail . lines

-- 
View this message in context: 
http://www.nabble.com/memoization-tp25306687p25400506.html
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] Would you mind explain such a code ?

2009-09-10 Thread staafmeister



zaxis wrote:
 
 myFoldl :: (a - b - a) - a - [b] - a
 
 myFoldl f z xs = foldr step id xs z
 where step x g a = g (f a x)
 
 I know myFoldl implements foldl using foldr. However i really donot know
 how it can do it ?
 
 Please shed a light one me, thanks!
 

Hi,

Nice example! Well this is indeed an abstract piece of code. But basically
foldl f z xs starts with z and keeps applying (`f`x) to it
so for example foldl f z [1,2,3] = ((`f`3).(`f`2).(`f`1)) z

Because functions are first-class in haskell, we can also perform a foldl
where instead of calculating the intermediate values we calculate the
total function, i.e. ((`f`3).(`f`2).(`f`1)) and apply it to z.

When the list is empty z goes to z, so the start function must be id.
So we can write
(`f`3).(`f`2).(`f`1) = foldr (\x g - g . (`f`x)) id xs

This is almost in your form.

Hope this helps,
Gerben
-- 
View this message in context: 
http://www.nabble.com/Would-you-mind-explain-such-a-code---tp25377949p25378268.html
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] memoization

2009-09-10 Thread staafmeister

Thanks to reactions!

What do you think about such a function? This function is
still a bit dangerous (I think). I don't know how to make
sure the compiler does not lift cache to something global.

But on the other hand this use of unsafePerformIO is legit
because it doesn't alter the referential transparency of 
the function. The same as in DiffArray.

Greetings
Gerben

memo f =
  let cache = unsafePerformIO $ newIORef M.empty
  cachedFunc x = unsafePerformIO (do
   m - readIORef cache
   case M.lookup x m of
 Just y - return y
 Nothing - do let res = f x
   writeIORef cache $ M.insert x res m
   return res)
  in cachedFunc

memo2 f = curry $ memo $ uncurry f

-- 
View this message in context: 
http://www.nabble.com/memoization-tp25306687p25381881.html
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: Re[Haskell-cafe] [2]: memoization

2009-09-10 Thread staafmeister


Hi Bulat,


Bulat Ziganshin-2 wrote:
 
 Hello staafmeister,
 
 Thursday, September 10, 2009, 3:54:34 PM, you wrote:
 
 What do you think about such a function? This function is
 
 a bit of refactoring
 
 -- global variable in haskell way
 cache = unsafePerformIO $ newIORef M.empty
 
 memo f x = unsafePerformIO$ do
m - readIORef cache
case M.lookup x m of
  Just y - return y
  Nothing - do let res = f x
writeIORef cache $ M.insert x res m
return res
 
 memo2 = curry . memo . uncurry
 

This doesn't work and is exactly what I'm afraid the compiler is going to
do. Cache needs to
be associated with the function f.

Otherwise one would get conflicts

Greetings
-- 
View this message in context: 
http://www.nabble.com/memoization-tp25306687p25382341.html
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] memoization

2009-09-05 Thread staafmeister


Hi,

I participating in de google code jam this year and I want to try to use
haskell. The following 
simple  http://code.google.com/codejam/contest/dashboard?c=90101#s=p2
problem 
would have the beautiful haskell solution. 

import Data.MemoTrie
import Data.Char
import Data.Word
import Text.Printf

newtype ModP = ModP Integer deriving Eq

p=1

instance Show ModP where
  show (ModP x) = printf %04d x

instance Num ModP where
  ModP x + ModP y = ModP ((x + y) `mod` p)
  fromInteger x = ModP (x `mod` p)
  ModP x * ModP y = ModP ((x * y) `mod` p)
  abs = undefined
  signum = undefined

solve _ [] = 1::ModP
solve [] _ = 0::ModP
solve (hs:ts) t@(ht:tt) | hs==ht = solve ts tt + solve ts t
| otherwise = solve ts t

go (run, line) = Case #++show run++: ++show (solve line welcome to code
jam)

main = interact $ unlines . map go . zip [1..] . tail . lines


Which is unfortunately exponential.

Now in earlier thread I argued for a compiler directive in the lines of {-#
Memoize function -#},
but this is not possible (it seems to be trivial to implement though). Now I
used memotrie which
runs hopelessly out of memory. I looked at some other haskell solutions,
which were all ugly and
more clumsy compared to simple and concise C code. So it seems to me that
haskell is very nice
and beautiful until your are solving real algorithmic problems when you want
to go back to some
imperative language.

How would experienced haskellers solve this problem?

Thanks
-- 
View this message in context: 
http://www.nabble.com/memoization-tp25306687p25306687.html
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] Question about Lazy.IO

2009-09-01 Thread staafmeister


Hi,

I've been wondering about Lazy IO for a while. Suppose we have a program
like

main = interact (unlines . somefunction . lines)

then somefunction is a pure function. With the semantic interpretation of:
given a input list
return an output list. However I, the user, can change my input depending on
the output of this
function. Now in simple cases like this, this will not be a problem. But
suppose you are reading
and writing to a file. Now the result of pure functions become dependent on
the order of execution,
breaking (I think) referential transparency. Am I wrong here or how could
you prove that Lazy IO
is consistent nonetheless?

Greetings,
Gerben

-- 
View this message in context: 
http://www.nabble.com/Question-about-Lazy.IO-tp25236848p25236848.html
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] Question about Lazy.IO

2009-09-01 Thread staafmeister


Dear Luke,

Thanks for your reply. I am interested in a more detailed explanation. If
it's
to long for this forum you can also mail it to me.

In response to your answer. In your program the user is also a pure
function. But I,
as a user, am not pure so I can do side effects. More specific suppose I
program something like this

ss - hGetContent handle (lazy IO)
dosomethingweird handle ss (a function that alters the file at will)

Now as a programmer I should be positive that ss will be the file as it was
before dosomethingweird modifies it. But this can never be guaranteed if ss
is lazy. And now things start to depend on the order of evaluation breaking
referential transparency, or do I overlook something.

For concreteness suppose dosomethingweird appends ss to the end of the
file. If ss is strict then it just copies the whole file, if ss is lazy it
copies the
whole file an infinite number of times.

Gerben


-- 
View this message in context: 
http://www.nabble.com/Question-about-Lazy.IO-tp25236848p25238044.html
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: Re[Haskell-cafe] duction Sequence of simple Fibonacci sequence implementation

2009-08-28 Thread staafmeister


Thanks for the memo trick! Now I understand that the haskell compiler
cannot memoize functions of integers, because it could change the space
behaviour. However I think it could memoize everything else. Because all
types that are data objects sitting in memory (so the arg is essentially a
reference)
can be memoized, without changing the space properties (except for overall
constants). Does haskell do this? And if it doesn't can you turn it on?

Cheers, Gerben
-- 
View this message in context: 
http://www.nabble.com/Reduction-Sequence-of-simple-Fibonacci-sequence-implementation-tp25178377p25187256.html
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: Re[Haskell-cafe] [2]: Reduction Sequence of simple Fibonacci sequence implementation

2009-08-28 Thread staafmeister



Bulat Ziganshin-2 wrote:
 
 
 this graph can share computations in only one way - when you give
 sharec node a name and use this name twice. for example, the following
 
 sum[1..1000] + prod[1..1000]
 
 don't share anything, but this
 
 let list = [1..1000]
 in sum list + prod list
 
 share the list. performing sharing via explicit naming common
 subexpressions is the only way to memoize results
 
 you imagine something highly inefficient like storing results of every
 computation ever done. are you think it really makes a sense?
 
 

Well in case I call (prod list) again it could lookup the reference and see
that this computation has already been performed and just lookup the answer.
In case `list' becomes GCed the GC should also destroy the lookup in the
cache.
The overhead is a O(1) overhead for the function because it needs to check
if
a computation has already performed. And the space overhead is not so big
because
every data object in memory there are a couple of references to be stored in
lookup tables.
So although there is space overhead it is not excessive.

-- 
View this message in context: 
http://www.nabble.com/Reduction-Sequence-of-simple-Fibonacci-sequence-implementation-tp25178377p25187710.html
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: Re[Haskell-cafe] [2]: Re[2]: Reduction Sequence of simple Fibonacci sequence implementation

2009-08-28 Thread staafmeister



Bulat Ziganshin-2 wrote:
 
 Hello staafmeister,
 
 Friday, August 28, 2009, 2:34:07 PM, you wrote:
 Well in case I call (prod list) again it could lookup the reference and
 see
 
 so it should keep a list of all values ever computed in program,
 together with their expressions? :) are you like idea of prod[1..10^6]
 computation taking 10 mbytes of memory?
 
 

The list you give prod is also 10 MB so it not a terribly inefficient
program.
It's a factor of 2. Well haskell also has often a factor of 2 overhead with
respect to C and people are not terribl concerned about that
-- 
View this message in context: 
http://www.nabble.com/Reduction-Sequence-of-simple-Fibonacci-sequence-implementation-tp25178377p25188000.html
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: Re[Haskell-cafe] [2]: Re[2]: Reduction Sequence of simple Fibonacci sequence implementation

2009-08-28 Thread staafmeister



david48 wrote:
 
 On Fri, Aug 28, 2009 at 1:03 PM, staafmeisterg.c.stave...@uu.nl wrote:
 
 
 The list you give prod is also 10 MB so it not a terribly inefficient
 program.
 
 That list takes memory only if it is forced. If it is passed to a lazy
 function, all the list may not be in memory at once.
 

In that case the GC cleaned up the whole list and while cleaning up it
should also clean up the references in the cache lookup table. So then 
there is no space overhead either. 

-- 
View this message in context: 
http://www.nabble.com/Reduction-Sequence-of-simple-Fibonacci-sequence-implementation-tp25178377p25188238.html
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: Re[Haskell-cafe] [2]: Re[2]: Re[2]: Reduction Sequence of simple Fibonacci sequence implementation

2009-08-28 Thread staafmeister



Bulat Ziganshin-2 wrote:
 
 Hello staafmeister,
 
 Friday, August 28, 2009, 3:03:13 PM, you wrote:
 so it should keep a list of all values ever computed in program,
 together with their expressions? :) are you like idea of prod[1..10^6]
 computation taking 10 mbytes of memory?
 
 The list you give prod is also 10 MB so it not a terribly inefficient
 program.
 
 no, it's produced on need so it needs O(1) memory
 
 It's a factor of 2. Well haskell also has often a factor of 2 overhead
 with
 respect to C and people are not terribl concerned about that
 
 factor of 2 compared to ALL VALUES ever produced when evaluating
 program. since computer performs about 10^9 computations per second,
 you are going to store 10^9 values each second, some of those may be
 multi-megabyte by itself
 
 

Hi Bulat,

All the values that are computed but are also GCed (and they will be, 10^9
bytes 
is the mem limit). If the GC removes a value then all references in cache to
those 
values can also be removed.

Gerben

-- 
View this message in context: 
http://www.nabble.com/Reduction-Sequence-of-simple-Fibonacci-sequence-implementation-tp25178377p25188333.html
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] (no subject)

2009-08-22 Thread staafmeister


Thank you for the reply.


Thomas ten Cate wrote:
 
 Although you most certainly can use a State monad, in most problems
 this isn't necessary. Most algorithms that you need to solve
 programming contest problems can be written in a purely functional
 style, so you can limit monadic code to just a few helper functions.
 

Yes I know but there are a lot of problems requiring O(1) array updates
so then you are stuck with IO again


Thomas ten Cate wrote:
 
 For example, this reads input in the style you mention (assuming the
 strings don't contain whitespace):
 
 import Control.Monad

 answer = id

 parse [] = []
 parse (s:p:r) = (s, (read p) :: Int) : parse r

 run = getLine  getLine = putStrLn . show . answer . parse . words

 main = flip replicateM_ run = readLn
 
 The answer function would be a pure function that computes the answer
 for a particular run. This main function is reusable for all problems
 with many runs.
 
 Observe that the number of edges (e), provided as a convenience for
 memory allocation in many other languages, is not even necessary in
 Haskell :)
 

Yes you're main is short. But how would you do it elegantly if 
instead of line breaks and spaces one would have only spaces.
Every thing on one big line. My C code would not mind one bit.


Thomas ten Cate wrote:
 
 (If anyone knows a better way than explicit recursion to map over a
 list, two elements at a time, or zip its even elements with its odd
 elements, I'd love to hear! I can imagine a convoluted fold with a
 boolean in its state, but it's ugly.)
 

Yes I missed such a function in a couple of problems I wanted to solve.
I would expect a generic function
groupN::Int - [a] - [[a]]
that groups a list into groups of N

Best,
Gerben
-- 
View this message in context: 
http://www.nabble.com/%28no-subject%29-tp25088427p25094244.html
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] (no subject)

2009-08-21 Thread staafmeister



Don Stewart-2 wrote:
 
 G.C.Stavenga:
 
 
 Hi, I'm just started to learn Haskell. Coming from a programming contest
 background (where it is important to be able to solve problems in a small
 amount of code) I'm wondering what the best way is for simple IO.
 
 A typical input file (in a programming contest) is just a bunch of
 numbers
 which you want to read one by one (sometimes interspersed with strings).
 In
 C/C++ this is easily done with either scanf or cin which reads data
 separated by spaces. In Haskell I have not found an equally
 satisfactionary
 method. The methods I know of
 
 1) Stay in the IO monad and write your own readInt readString functions.
 A lot
 of code for something easy.
 
 2) Use interact together with words and put the list of lexemes in a
 State
 monad and define getInt where at least you can use read.
 
 3) Use ByteString.Char8 which has readInt (but I couldn't find a
 readString). But one has to put it also in a State monad.
 
 I think that there must be standard function that can do this. What do
 experienced Haskellers use?
 
 
 map read . lines
 
 Thank you for the reply. But this only works for if you read only integers
 all on different lines.
 But in general you have a structure like
 
 first line -- integer specifying the number of testcases (n)
 Then for each testcase 
 a line with an integer specifying the number of edges (e)
 a line with e pairs of string s and int p where p is the number asociated
 with string s, etc.
 
 Such a structure cannot be parsed by map read.lines
 What I used is words to tokenize and put the list in a State monad with
 readInt, readString, etc. functions, to mimic
 C code. This seems to be a lot of overkill, so there must be an simpler
 way
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/%28no-subject%29-tp25088427p25088830.html
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