Monadic Call/CC?

2002-02-20 Thread Ashley Yakeley

Has anyone investigated monadic call-with-current-continuation in 
Haskell? Given this:

class (Monad m) => PeirceMonad m where
{
peirceM :: ((a -> m b) -> m a) -> m a;
};

...which Monads can be made PeirceMonads?

The corresponding non-monadic function:

peirce :: ((a -> b) -> a) -> a;

probably can't be defined.


-- 
Ashley Yakeley, Seattle WA

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



Re: forcing IO operations

2002-02-20 Thread Jay Cox

On Thu, 21 Feb 2002, Andre W B Furtado wrote:

> > >liftIOtoMyMonad_ :: IO () -> MyMonad ()
> > >liftIOtoMyMonad_ m   = liftIOtoMyMonad' (const m) ()
>
> I'm having problems compiling this one: "The last statement in a 'do'
> construct must be an expression"


No problems here using no flags either.  ghc-5.00
Hmmm... hugs Feb2001 seems to complain about my source (different reason).

Which version of which compiler?

(Btw, upon further review I cant think of a good reason for that function
to exist.  liftIOtoMyMonad can do anything liftIOtoMyMonad_ can handle.
Essentially liftIOtoMyMonad_ = liftIOtoMyMonad but with a much more
restrictive type)


Jay Cox


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



Re: forcing IO operations

2002-02-20 Thread Andre W B Furtado

[answering myself...]


> > >liftIOtoMyMonad_ :: IO () -> MyMonad ()
> > >liftIOtoMyMonad_ m   = liftIOtoMyMonad' (const m) ()
>
> I'm having problems compiling this one: "The last statement in a 'do'
> construct must be an expression"

The problem is not related with liftIOtoMyMonad_ , but with liftIOtoMyMonad
and liftIOtoMyMonad'. I think its an identation problem. Re-writing these
funcions as follows solves the problem:

>liftIOtoMyMonad' :: (a -> IO ()) -> a -> MyMonad ()
>liftIOtoMyMonad' p q =
> StateMonad $ \s -> (do p q
>return ((),s))
>
>liftIOtoMyMonad  :: IO a -> MyMonad a
>liftIOtoMyMonad p=
> StateMonad $ \s -> (do y <- p
>return (y,s))


At least by now, all the ideas are working very well... great help Jay,
thanks a lot!

-- Andre

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



Re: forcing IO operations

2002-02-20 Thread Andre W B Furtado

> >liftIOtoMyMonad_ :: IO () -> MyMonad ()
> >liftIOtoMyMonad_ m   = liftIOtoMyMonad' (const m) ()

I'm having problems compiling this one: "The last statement in a 'do'
construct must be an expression"

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



Re: forcing IO operations

2002-02-20 Thread Jay Cox

On Wed, 20 Feb 2002, Andre W B Furtado wrote:

> hi, you sent me "blank" email (nothing besides my own message). Were you
> trying to tell something? :)
>
> -- Andre

Heh, actually I was.

I curse the day that the designers of pine put (control-X) for sending
a letter next to (control-C) for killing it :)


Please don't take offense to this, but do you feel unsafePerformIO
is really necessary for your application?

There's got to be another way...

In Systematic Design of Monads [1] there is given a systematic method to
wrap monads around other monads. I was going to email you an example
monad which wraps around the IO monad.  Granted, its a state monad wrapped
around the IO monad, which may not be of much use except for
organizational purposes.

I've essentially stolen the design from the aforementioned paper, but
since the paper appears to be for Gofer, the Haskell precursor, I decided
to modernize it a bit.

By the way, seems like there might be something along the lines of this
in the hugs library.  (If not, I'm sure I remember something about reader
and writer monad wrappers)

Jay Cox

[1]written by John Hughes & Magnus Carlson (1996)
Appologies to both since I cant give a more specific reference to the
paper. John (or Magnus), you wouldn't have happened to taken the time to
have updated the code from that paper, have you?  If you already have, I
appologize for not refering to it and using it as well :)





If you cut and paste the following lines I think they ought to be able to
run as in a haskell.lhs source file.


You proposed using some runMyMonad function.  in order to
combine IO actions with your code the runction returns and IO (blah).
see, the IO is hidden within the new monad but IO actions are still being
threaded through MyMonad.




>newtype MyNewStateMonad m s a = StateMonad (s -> m (a,s))
>
>
>bindST (StateMonad x) f =
>   StateMonad (\s -> ( x s >>= \(v,s') -> let StateMonad g = f v in g s'))
>
>unitST v = StateMonad (\s -> return (v,s))
>
>
>instance Monad m => Monad( MyNewStateMonad m s) where
>  (>>=) = bindST
>  return = unitST
>
>
>type MyMonad a = MyNewStateMonad IO Int a
>
>runMyMonad :: MyMonad a -> Int ->IO (a,Int)  -- (a,Int) the state tuple
>runMyMonad (StateMonad f) = f



that's it!
the remainder is mostly example code
it:

1. lifts print and getLine to monadic actions under MyMonad (aka
MyNewStateMonad IO Int)

2. has an example monadic action (add50toMyMonadState) which has
absoultely nothing to do with the underlying IO monad.

3. lifted a sequence of IO actions to be executed under MyMonad via
arbitrarysequence

4. combines all the actions under MyMonad into monad_actions so that
they may be run with runMyMonad.



note the line:
y<- runMyMonad monad_actions 0

the 0 initializes the state of the MyMonad,  (hence this is why runMyMonad
is typed MyMonad a -> Int ->IO (a,Int) )




>liftIOtoMyMonad' :: (a -> IO ()) -> a -> MyMonad ()
>liftIOtoMyMonad' p q =
> StateMonad $ \s -> do p q
>   return ((),s)
>
>liftIOtoMyMonad  :: IO a -> MyMonad a
>liftIOtoMyMonad p=
> StateMonad $ \s -> do y <- p
>   return (y,s)
>
>liftIOtoMyMonad_ :: IO () -> MyMonad ()
>liftIOtoMyMonad_ m   = liftIOtoMyMonad' (const m) ()
>
>
>getLineMM = liftIOtoMyMonad getLine
>printMM = liftIOtoMyMonad' print
>arbitrarysequence =
>liftIOtoMyMonad $
>   do print "What's your name?"
>  name <-getLine
>  print $ "Your name is " ++ name
>
>
>add50toMyMonadState :: MyMonad ()
>add50toMyMonadState = StateMonad(\s -> return ((),50+s))
>
>
>monad_actions=   do arbitrarysequence
>printMM "What's your password"
>pass <- getLineMM
>printMM ("Your password is: " ++ pass)
>add50toMyMonadState
>return 3
>
>
>main = do y<- runMyMonad monad_actions 0
>  print $ "State:" ++ show (snd y) ++ " Value:" ++ show (fst y)


If you are reading this you should be  instead copying it to some file
and playing with it instead!

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



RE: foralls in class assertions

2002-02-20 Thread Simon Peyton-Jones

OK, so it does look as though it's the same idea as 
that described in our paper.   Good.

I have not implemented, yet.  As always my implementation
priorities are strongly influenced by my perception of whether
some enhancement would be used.  Maybe you can outline
why such a change would be useful to you?  I only have the
example in our paper as motivation so far.

Simon

| -Original Message-
| From: Ashley Yakeley [mailto:[EMAIL PROTECTED]] 
| Sent: 20 February 2002 01:08
| To: Simon Peyton-Jones; Haskell List
| Subject: RE: foralls in class assertions
| 
| 
| At 2002-02-19 09:21, Simon Peyton-Jones wrote:
| 
| >I don't know if it makes sense.   You've written down some syntax,
| >but it's not clear to me what you intend by it.
| 
| Hmm... it should be straightforward...
| 
| > instance (forall a. Eq a => Eq (f a)) => Eq (Rose f a) where..
| 
| I assume that the 'a' quantified in (forall a. ...) is not 
| the same as 
| the 'a' in 'Rose f a'?
| 
| >| instance
| >| (
| >| forall a. HasIdentity (m a a),
| >| forall a b c. Composable (m b c) (m a b) (m a c)
| >| ) =>
| >|  Category m;
| 
| This means 'if for all a, "HasIdentity (m a a)", and also for 
| all a b c, 
| "Composable (m b c) (m a b) (m a c)", then "Category m"'.
| 
| "(forall a. HasIdentity (m a a))" as a class assertion declares a 
| property of m. It says that for all types a, there's an instance 
| "HasIdentity (m a a)".
| 
| >| Or even allow the foralls their own context:
| >| 
| >| foo :: (forall a. (C a b) => D a c) => T b c;
| 
| This means foo has type (T b c), where for every type a for 
| which there's 
| an instance "C a b", there's an instance "D a c".
| 
| >| class
| >| (
| >| forall a. HasIdentity (m a a),
| >| forall a b c. Composable (m b c) (m a b) (m a c)
| >| ) =>
| >|  Category m;
| 
| Personally I think the 'superclass' arrow in class 
| declarations should 
| point the other way, as in '<='. After all, instances of the 
| class imply 
| instances of the superclasses, not the other way around.
| 
| But that aside, this means '"Category" is a class on m, 
| provided that for 
| all types a, there's an instance "HasIdentity (m a a)", and 
| also for all 
| types a b c, there's an instance "Composable (m b c) (m a b) 
| (m a c)"'.
| 
| 
| -- 
| Ashley Yakeley, Seattle WA
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Haskell 98 Report

2002-02-20 Thread Simon Peyton-Jones

I don't want to do that until its finished!
Which I earnestly hope will be soon.

Simon

| -Original Message-
| From: David Feuer [mailto:[EMAIL PROTECTED]] 
| Sent: 20 February 2002 08:43
| To: [EMAIL PROTECTED]
| Subject: Haskell 98 Report
| 
| 
| Is the revised Haskell98 report going to be put in its proper 
| place on the web site any time soon?  As it is, it is sitting 
| off to the side while the old Report sits in the seat of honor.
| 
| David Feuer
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Final CFP : FLOPS'02 / ASIA-PEPM'02

2002-02-20 Thread Zhenjiang Hu

===
The submission deadline for ASIA-PEPM'02 and FLOPS'02 
has ben extended until March 8, 2002.
===

   FINAL CALL FOR PAPERS 

ASIAN Symposium on
  Partial Evaluation and Semantics-Based Program Manipulation
   http://www.comp.nus.edu.sg/asia-pepm02

   International Symposium on Functional and Logic Programming 
 http://www.ipl.t.u-tokyo.ac.jp/FLOPS2002/
   
   Aizu, JAPAN, September 12-17 2002

***

IMPORTANT DATES:

Submission Deadline: March 8, 2002  
Notification:May 21, 2002
Final Version:   June 25, 2002   
Conferences: September 12-17, 2002  

***


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



Haskell 98 Report

2002-02-20 Thread David Feuer

Is the revised Haskell98 report going to be put in its proper place on
the web site any time soon?  As it is, it is sitting off to the side
while the old Report sits in the seat of honor.

David Feuer
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell