Re: more parsing paper

2002-01-24 Thread Martin Norbäck

ons 2002-01-23 klockan 22.18 skrev David Feuer:
 The paper I am reading uses the following in an instance declaration for
 parsers:
 
 p = f = Parser (\cs - concat [parse (f a) cs' |
(a,cs') - parse p cs])
 
 Isn't this the same as
 
 p = f = Parser (\cs -
  [(a',cs'') | (a,cs') - parse p cs,
 (a',cs'') - parse (f a) cs'])
 ?
 
 If so, any guesses why they chose the more obscure form?

Why do you say that the first form is less obscure? It uses less
bindings, and the non-obscure standard function concat.

Your version could be simplified, though, by replacing the expression
(a',cs'') with a single name.

Regards,

Martin

-- 
[ http://www.dtek.chalmers.se/~d95mback/ ] [ PGP: 0x453504F1 ] [ UIN:
4439498 ]
Opinions expressed above are mine, and not those of my future
employees.
SIGBORE: Signature boring error, core dumped


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



Re: Monad composition

2002-01-24 Thread John Hughes

The easiest way to combine State and IO is using a monad transformer. There
are some lecture notes which you might find useful at

http://www.md.chalmers.se/~rjmh/Combinators/Monads/index.htm

which refer to a library module

http://www.md.chalmers.se/~rjmh/Combinators/MonadTransformers.hs

Using this library you just build the type

type StateIO s a = State s IO a

which is a monad with operations readState, writeState, and

lift :: IO a - StateIO s a

John 

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



Re: performance of monads

2002-01-24 Thread Jorge Adriano


 I agree with others who mentioned that viewing monads as simply
 providing a way to sequentialize things or to program imperatively is
 the wrong way to look at them.  
snip
Yes, Lists are the classical example.


 That said, the EFFICIENCY of monads is often poorly understood.  To
 state the obvious, just because you program something in a monad doesn't
 make it efficient.  In particular, a state monad does not guarantee that
 the state will actually be updated in place.  The monad only hides the
 state, and creates an OPPORTUNITY for it to be updated in place.  But,
 for example, if you add an operation that returns the entire state as a
 value, then the single-threadedness property is in fact lost, and
 in-place update becomes as problematical as it always is.
Well... I'm having *lots* of problems here. :-)

I've felt need to use State monads in two distinct situations:
(A) Keep track of data,
Example:
- Genetic Algorithms
how many crossovers, mutations, etc
best (or average) individual fitness in each generation
some schemata evolution
etc...
- Neural Networks
Weights evolution
Error evolution
etc...

(B) Acessing state
There are some situation where you'll probably rather hide some 
implementation details in some state monad instead of passing around lots of 
values...
Example:
- Genetic Algorithms:
Getting Rand. Numbers (instead of passing around all the StdGens you need)
etc...



And I've seen two distict aproaches. Using a State monad like one provided 
with GHC (1), or a state monad like the one defined in the paper Moands for 
the Working Haskell Programmer (2).

In (1), I can see how I can take advantage of the monad and make updates in 
place using referencies. But then you'll have to either:
- pass the referencies as a parameter to the functions where you use them
(needless too say that this defeats the (my) main purpose of using a state 
monad which is in case A, keep track of data with minimal signature change )

- encapsulate all the functions in the monad.
I don't really like this solution... you won't be even able to test the 
functions in the interpreter...

- using implicit referencies (?)
Haven't thought that much about this one yet


In (2), I can't really see how to make updates in place... I still didn't 
figure out how to make my own State monad and use updates in place.
What I did was 
- Define my state as some record (datatype with field labels)
- Create functions to get and update state...

This is doomed to fail!
Even if I only want to update the state (like adding values to lists of 
values or incrementing some counters), I'll have to access that same state.
So I'll have to make my own getStateField functions and updateStateField 
functions for every single field.
Using datatypes with field labels makes it easy to define functions to get 
State fields (you get the would state then use the projection function)... 
but to update some field state it gets more complicated, if you got 6 
counters, you'll have to write similar code 6 times...
Damn, I seem to be waisting more time and writing more lines of code than if 
I was doing it in Pascal!! All just to keep track of some data, it is not 
even really 'part of the algorithm', I just want to evaluate how it is 
behaving
Efficiency wise it seems pretty bad, no updates in place, and I'm expecting 
lots of stack overflows unless I take special care dealing with laziness.


My problem with this is that I'm trying to do something trivial here..., 
forget about (B) (accessing state), I just want to keep track of data, any 
newbie can do that in the imperative world, and it seems like some pretty 
advanced stuff in here!!
Programmers need to do this all the time, there should be some simple, well 
documented, way to do it. I don't want to be a monads expert to be able to do 
this kind of thing... (and I'm the kind of guy that wants to, eventually, 
become an monad expert... just not now... imagine how some other guy that has 
no interest in monads feels when he has the same problem.)

IMO (and maybe I'm wrong... this is just the way I feel right now) either we 
are missing some simple aproach here, or at least we do not have at all the 
adequate documentation about it, at all.


Another state issue, sometimes I have some values that I want to keep 
constant through the whole algorithm.
Example:
(some very simple NNs for instance)
- learning rate
- activation function 
- maximum number of steps
- minimum error required

So I'll just declare them as 'constants'. But what if I decide I want the 
user to be able to chose? Now I got two options:
- pass them around as values to all the functions - And signatures get HUGE
- just pass them to a higher level function that will encapsulate the 
functions that use them... which is ugly and complicates everything because 
you can't test the lower level functions in the interpreter. 

Am I missing something here or is this really the best you can do?


 This is an issue that I and my student 

Re: Monad composition

2002-01-24 Thread Andre W B Furtado

Well, it's also possible to interchange data between these two monads by:

unsafeIOToST :: IO a - ST s a
stToIO :: ST s a - IO a

Can anyone tell the possible problems related to
unsafeIOToST?
^^

-- Andre

- Original Message -
From: Tom Bevan [EMAIL PROTECTED]
To: Andre W B Furtado [EMAIL PROTECTED]
Cc: Haskell Cafe List [EMAIL PROTECTED]
Sent: Thursday, January 24, 2002 4:13 AM
Subject: Re: Monad composition


 Andre,

 I can't work out how it should be done.
 The way I see it, the StateIO monad should have four functions
 associated with it.
 1/ update - a function to update the state
 2/ retrieve - a function to retrieve the state from the monad
 These two are inherited from the standard State monad
 3/ input - make a character from stndIn available to the state
 transformation functions
 4/ output - send the state of the monad after a certain set of
 transformations to stndOut

 I've managed to write functions 1-3 but not 4.

 Here's my work so far.I'm not really sure if this is on the right track.

 Tom


 On Thu, 2002-01-24 at 14:32, Andre W B Furtado wrote:
  Hi, I have the same problem. Did anyone answered your question?
 
  Thanks,
  -- Andre
 
  - Original Message -
  From: Tom Bevan [EMAIL PROTECTED]
  To: Haskell Cafe List [EMAIL PROTECTED]
  Sent: Wednesday, January 23, 2002 4:29 AM
  Subject: Monad composition
 
 
  
   Hi all,
  
   I'm writing a programme which requires IO actions to be interleaved
with
   operations on a State monad. From what I can work out, this means that
   the IO Monad and the StateTransformation monad need to be composed
into
   a single highr order monad.
   Does anyone have any references or pointers on how this should be
done?
  
  
   Tom
  
  
  
   ___
   Haskell-Cafe mailing list
   [EMAIL PROTECTED]
   http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 




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



Re: Monad composition

2002-01-24 Thread Theodore Norvell

Tom Bevan wrote:
 
 Hi all,
 
 I'm writing a programme which requires IO actions to be interleaved with
 operations on a State monad. From what I can work out, this means that
 the IO Monad and the StateTransformation monad need to be composed into
 a single highr order monad.
 Does anyone have any references or pointers on how this should be done?

I'd also be interested in references or pointers.  While, the
logic isn't hard to get right, it is easy to make do-it-yourself
state monads lazier than you intended.

Below is how I've done it in one project.  I'd be interested in any 
comments from others on this code.  I had two other requirements
beyond what you mention. I wanted to be able to stop the computation
in the middle (in case an error was detected, for example). Hence the
use of the Ok_Err type.  Also, I wanted to make sure that each state
is evaluated before moving on to the next step of the computation;
this explains the ubiquitous use of seq. You also have to
make sure that the constructors for the state are strict and generally
be careful that after you've computed a new state the last state is garbage.

BTW the Ex in StateExTrans stands for exception, but this monad
doesn't support exception handling yet, so this is a misnomer.

Cheers,
Theodore Norvell


Dr. Theodore Norvell   [EMAIL PROTECTED]
Electrical and Computer Engineeringhttp://www.engr.mun.ca/~theo
Engineering and Applied Science
Memorial University of Newfoundland
St. John's, NF, Canada, A1B 3X5

Currently visiting the Department of Computer Science and ICICS at the
University of British Columbia. See my webpage for contact details.

-Here is the monad-

module StateExMonad( Ok_Err(..),
 StateExTrans(),
 runSET,
 stop,
 for,
 getState,
 putState,
 command,
 expression,
 doIO )
where

data Ok_Err s a = Ok s a | Err
data StateExTrans s a = SET (s - IO (Ok_Err s a))

instance Functor  (StateExTrans s) where
--fmap :: (a - b) - (StateExTrans s a - StateExTrans s b)
fmap f x = do a - x
  return (f a)
   
instance Monad (StateExTrans s) where
-- return :: a - StateExTrans s a
return a = SET (\ s - seq s (return (Ok s a)))
-- = :: (StateExTrans s a) - (a - StateExTrans s b) -
--  (StateExTrans s b)
(SET st) = f
= SET(\ s -
  seq s (do ok_err' - st s
case ok_err' of
  (Ok s' a) -
   let (SET st') = f a
   in st' s'
  Err -  return Err))

runSET :: StateExTrans s a - s - (IO (Ok_Err s a))
runSET (SET f) s = f s

stop :: StateExTrans s a
stop = SET(\s - return Err)

for :: (Functor m, Monad m) = [i] - (i - m a) - m [a]
for [] p = return []
for (i:rest) p = p i = (\a - fmap (a:) (for rest p))

getState = SET (\s - seq s (return (Ok s s)))

putState s = SET (\_ - seq s (return (Ok s (

command :: (s - s) - StateExTrans s ()
command c = SET(\s - seq s (return (Ok (c s) (

expression :: (s - a) - StateExTrans s a
expression e = SET(\s - seq s (return (Ok s (e s

doIO :: (IO a) - StateExTrans s a
doIO io' = SET(\s - seq s (io' = (\a - return (Ok s a)))

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



Re: Monad composition

2002-01-24 Thread Rijk-Jan van Haaften

Andre W B Furtado wrote:
Well, it's also possible to interchange data between these two monads by:

unsafeIOToST :: IO a - ST s a
stToIO :: ST s a - IO a

Can anyone tell the possible problems related to
unsafeIOToST?
^^

Probably in the same manner as with unsafePerformIO:
it can break referential transparency.

changeFile fileName   = unsafePerformIO (writeFile fileName Hello, world)
fileContents fileName = unsafePerformIO (readFile  fileName)

Now, if there is a call to changeFile between two calls to fileContents with
the same filename (assumed that the file didn't contain the text Hello, 
world)
the function returns different answers in exactly syntactic identical calls.
Thus, referential transparency is broken.

Rijk-Jan van Haaften



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



Dynamic linking of Haskell modules?

2002-01-24 Thread senganb

I'd like to be able to dynamically load Haskell code
from a plugin binary file into a Haskell application,
just as I can dynamically load .so files into a C application.

Since ghci does this, I thought I could copy its implementation
but after looking into it, it's very complicated. I notice
that OCaml can do this (http://algol.prosalg.no/~malc/scaml/)

The only simple solution I can think of is to use FFI to export
the objects in the .so file as following the C interface, and then
importing them into the main Haskell application as C functions,
but the extra marshalling is ugly.

Has anyone solved this problem?
Are there any plans to support this in the future in ghc or a
third party library?

Sengan


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