[Haskell-cafe] Parsec Question

2006-01-09 Thread Gerd M
I'm trying to use parsec for parsing a custom input stream. As far as I 
understood the manual correctly I need to define the primitive parser:


type MyParser a   = GenParser (SourcePos,Tok) () a
mytoken :: (Tok - Maybe a) - MyParser a
mytoken test
 = token showToken posToken testToken
 where
   showToken (pos,tok)   = show tok
   posToken  (pos,tok)   = pos
   testToken (pos,tok)   = test tok

The problem is, since SourcePos is an abstract datatype, how can I actually 
run this parser without explicitly using values of type SourcePos in the 
input stream?


Many thanks in advance!

_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


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


[Haskell-cafe] Re: Parsec Question

2006-01-09 Thread Gerd M

despite SourcePos being abstract, it can be fully manipulated using newPos.

Thanks for the tip, I thought it wasn't exported.





Gerd M wrote:
I'm trying to use parsec for parsing a custom input stream. As far as I 
understood the manual correctly I need to define the primitive parser:


type MyParser a   = GenParser (SourcePos,Tok) () a
mytoken :: (Tok - Maybe a) - MyParser a
mytoken test
 = token showToken posToken testToken
 where
   showToken (pos,tok)   = show tok
   posToken  (pos,tok)   = pos
   testToken (pos,tok)   = test tok

The problem is, since SourcePos is an abstract datatype, how can I 
actually run this parser without explicitly using values of type SourcePos 
in the input stream?


_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


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


Re: [Haskell-cafe] Memoization

2005-10-08 Thread Gerd M
Thanks to everyone for the answers, I'm getting a picture now. Maybe I will 
give the memoizing Y combinator a try later.



On 2005-10-07 at 22:42- Gerd M wrote:
 As (memory) is a function, it
 cannot be memoized (the function can be, but not its result, which is
 what you're after).
 How can a funcion be memoized but not it's result (what does this 
mean)!?

 Since there are no side effects in Haskell why is it important that the
 array is a CAF? Or let's say it that way, why can't the results of a 
(pure)
 function be memoized since it always returns the same result for the 
same

 parameters?

I'm a bit rusty on this, but here's an attempt at an
explanation.

This is an implementation issue; a matter of choice for the
implementor. In a function like this:

 f x = factorial 100 + x

factorial 100 doesn't depend on x -- is a CAF -- so it can
be lifted out and computed only once. Note that since the
value of f doesn't depend on whether this is done, there's
no /requirement/ that the compiler do it.

In this:

 g a = \ x - factorial a + x

g 100 is equivalent to f, but here the factorial 100 isn't a
constant (it depends on a), so the compiler would have to go
to extra lengths (known as full laziness) to ensure that
the factorial was kept for each application of g. It's
certainly possible for a compiler to do this, but the
problem is that if the subexpression that gets retained is
infinite, it takes up a lot of space, and there's no way for
the programmer to say that it's no longer needed. So
compilers tend not to do this.

  Jón


--
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk




_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


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


[Haskell-cafe] Memoization

2005-10-07 Thread Gerd M

Hello,
I'm trying to use Data.Map to memoize computations. Unfortunately this 
didn't improve the runtime of f at all, so there must be something wrong 
with my implementation. Thanks in advance!


f 1 s (HMM s0 _   sts)  =  s ??? sts s0
f t s hmm = memory hmm Map.! (t,s)

memory hmm@(HMM s0 sss sts)
   = Map.fromList [ ((t,s),f' t s hmm) | t - [1..100], s - sss, 
s/=s0 ]


f' 1 s (HMM s0 _   sts)  =  s ??? sts s0
f' t s hmm@(HMM s0 sss sts)
   = sum [ (memory hmm)Map.!(t-1,s') * (s ??? sts s')  | s' - sss, s' 
/= s0 ]


_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


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


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Gerd M
I still don't get it. I changed my code to structurally match your example 
(see below) but the result is still the same...


f 1 s (HMM s0 _   sts)  =  s ??? sts s0
f t s hmm = memory hmm Map.! (t,s)

memory hmm@(HMM s0 sss sts)
= Map.fromList [ ((t,s),f' t s hmm) | t - [1..100], s - sss ]

f' 1 s (HMM s0 _   sts)  =  s ??? sts s0
f' t s hmm@(HMM s0 sss sts)
= sum [ (f (t-1) s' hmm) * (s ??? sts s')  | s' - sss ]



I would use an array, which has O(1) lookup...
Instead of changing your code, I'll give a bit more well-known example
(partially because I'm in a bit of a rush :-)). Here's a fib function
memoized for the first 100 n (using a general approach with arrays,
instead of the zipWith thing)

import Data.Array

fib 0 = 1
fib 1 = 1
fib n | n = 100 = fibarr!n
  | otherwise = fib' n

fibarr = listArray (2,100) [ fib' x | x - [2..100]]
fib' n = fib (n-1) + fib (n-2)

The array is lazy in its elements (but not its indices) so the array
of 100 fibs won't actually be computed until you request a fib (then
all fibs  n will be computed).
So basically, define an array which contains the value of the function
at each entry, make sure you use the array in defining these elements
if your function is recursive (top-level, it doesn't change the
correctness but if you define it in a local scope your implementation
probably won't save the entries in the array between calls which kinda
ruins the point of memoization!).


_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


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


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Gerd M
That's what I got from profiling, for some reason the memoized version is 
awfully slow:


Memoized version:
total time  =  143.74 secs   (7187 ticks @ 20 ms)
total alloc = 25,404,766,256 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

memory Main   96.9   99.0
con2tag_State# Main1.60.0


Non memoized version:
total time  =6.02 secs   (301 ticks @ 20 ms)
total alloc = 990,958,296 bytes  (excludes profiling overheads)

COST CENTREMODULE   %time %alloc

??? Prob   61.1   73.1
fMain   10.3   17.8
con2tag_State# Main7.60.0
sumProb   Prob6.61.5
tag2con_State# Main3.31.9
con2tag_Out#Main2.70.0
tag2con_Out#Main2.31.9
sumProb  Prob2.03.0
stateTrMain2.00.0
mul   Prob1.70.8




From: David Roundy [EMAIL PROTECTED]
To: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Memoization
Date: Fri, 7 Oct 2005 14:12:39 -0400

On Fri, Oct 07, 2005 at 06:08:48PM +, Gerd M wrote:
 I still don't get it. I changed my code to structurally match your
 example (see below) but the result is still the same...

How are you timing your function?
--
David Roundy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


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


Re: [Haskell-cafe] Memoization

2005-10-07 Thread Gerd M

This works, thanks a lot, you saved my day/night! :-)


As (memory) is a function, it
cannot be memoized (the function can be, but not its result, which is
what you're after).
How can a funcion be memoized but not it's result (what does this mean)!? 
Since there are no side effects in Haskell why is it important that the 
array is a CAF? Or let's say it that way, why can't the results of a (pure) 
function be memoized since it always returns the same result for the same 
parameters?


Regards



 ff t s hmm@(HMM s0 sss sts) = f t s
   where
f 1 s  =  s ??? sts s0
f t s  =  memory Map.! (t,s)

f' 1 s  =  s ??? sts s0
f' t s  =  sum [ (f (t-1) s') * (s ??? sts s')  | s' - sss ]

memory  =  Map.fromList [ ((t,s), f' t s) | t - [1..100], s - sss ]

...which is of course completely untested.  Of course, the memoizing
fixed point combinator Chris Okasaki posted a while ago would be far
more elegant, I'm just too lazy to dig it up.



_
FREE pop-up blocking with the new MSN Toolbar - get it now! 
http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/


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


Re: [Haskell-cafe] Newbie Question about Error Handling

2005-07-25 Thread Gerd M

We're being clever and returning from IO not a Char, but a MyMonad Char
(mimp).  Then, we run that, which either produces the answer we wanted,
or throws an error in MyMonad.

Thanks. That did the trick! :-)
Regards



However, it's still rather cumbersome, so here's a function similar to
liftError that works for your monad.

-- I'll assume you have such a function
fromIOError :: IOError - MyErrorType

-- The name is intended to convey that IO errors are caught and
-- reintroduced into MyMonad.  Better suggestions welcome.
liftIOTrap :: IO a - MyMonad a
liftIOTrap io = do mx - liftIO (do x - io
return (return x)
 `catchError`
 (\e - return (throwError
  (fromIOError e
   mx

foo :: MyMonad a
foo = do
inp - liftIOTrap (getChar
`catchError`
(\e - if isEOFError e then return 
'\0'
   else throwError 
e))

...

Andrew

[1] http://haskell.org/pipermail/haskell-cafe/2005-June/010361.html



_
Express yourself instantly with MSN Messenger! Download today it's FREE! 
http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/


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


[Haskell-cafe] Newbie Question about Error Handling

2005-07-24 Thread Gerd M

Hello!
I'm confused by the error handling in Haskell. I've written a program that 
uses a combined monad of type:

type MyMonad a = ErrorT MyErrorType (StateT MyStateType IO) a
(MyErrorType is an instance of Error)

Therefore, to handle IO Errors inside of MyMonad I need to write:
foo :: MyMonad a
foo = do ...
 inp - liftIO (getChar
   `catchError`
   (\e - if isEOFError e then return '\0'
  else return 
'?') )

 case inp of
  '\?' - throwError ...
  
 `catchError`
 myErrorTypeHandler
This of course is cumbersome and ugly and I'm sure there is a way to do 
better. Helpful advice is welcome!


_
FREE pop-up blocking with the new MSN Toolbar - get it now! 
http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/


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


[Haskell-cafe] Combining Haskell and Software Verification

2005-06-11 Thread Gerd M

Hello,
I have to do a larger project about Software Verification for university.
The methods and systems I've seen so far only concern imperative/OOP 
languages while there seems to be little concerning functional languages.


Since the exact topic can be choosen freely and I've already spent too many 
years messing around with OOP languages, I would like to do a project 
related to (or using a) functional language, especially Haskell. The problem 
is, up to now I wasn't successful in finding it.


Suggestions are _very_ welcome!

regards,
Gerd

_
Don't just search. Find. Check out the new MSN Search! 
http://search.msn.com/


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


[Haskell-cafe] Data structure for filesystem representation

2004-04-06 Thread Gerd M
Hello!

For an university project i need to design a data structure (in haskell) 
that's capable of representing a unix filesystem and therefore fast 
insertion/deletion. Support for persistent storage is also required.

Principally i was thinking to use a Binary Search Tree or an AVL Tree but 
since this is my first real world application in Haskell I'm not so sure if 
this is a good (performant) solution.
Any advice is welcome!

Regards,
Gerd.
_
MSN 8 with e-mail virus protection service: 2 months FREE* 
http://join.msn.com/?page=features/virus

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