Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-17 Thread Thomas Jäger
Hello,

I haven't followed this discussion very closely, but in case you want to
play with this sort of thing, you can check out the code from my
TMR-Article
http://www.haskell.org/tmrwiki/FunWithLinearImplicitParameters

Despite the wacky implementation it is actually surprisingly reliable,
modulo some (linear) implicit parameter quirks.

The [[1,2,3,4]] vs. [[1],[2],[3],[4]] ambiguity is resolved using the
same method as the borrow/<- proposal (by a function called `reflect');
and the function `reify' is corresponding to the enclosing do. A notable
difference is that my implementation always shows the information
whether a specific expression is a `monadic' one in the type. E.g.

*Reflection> reify [1,2,3,4] :: [[Int]]
[[1,2,3,4]]
*Reflection> [reify 1, reify 2,reify 3,reify 4] :: [[Int]]
[[1],[2],[3],[4]]
*Reflection> reify [reflect [1,2], reflect [3,4]] :: [[Int]]
[[1,3],[1,4],[2,3],[2,4]]

Here [reflect [1,2], reflect [3,4]] has the type Monadic [] [Int] (where
Monadic is a type synonym involving linear implicit parameters...).


However, when doing such a thing, one must decide for an evaluation
order. Because of the way it is implemented, my code uses Haskell's lazy
strategy but that makes reasoning about the resulting programs very hard
(though I believe it can be made precise):

*Reflection> reify (tail $ [reflect [1,2],3,4]) :: [[Int]]
[[3,4]]
*Reflection> reify (tail $!! [reflect [1,2],3,4]) :: [[Int]]
[[3,4],[3,4]]

(here, $!! is deepSeq'ed application)

An eager strategy might be less obscure, but suffers from the problems
described by Ben. It should also be noted that a Call-By-Name-like
strategy can be emulated with appropriate types, as in:

*Reflection> reify (let x :: Monadic [] Int; x = reflect [1,2] in [x,x])
[[1,1],[1,2],[2,1],[2,2]]
*Reflection> reify (let x :: Int; x = reflect [1,2] in [x,x])
[[1,1],[2,2]]

Of course, in case of no explicit type signature, the monomorphism
restriction plays an infamous role and the behavior depends on the flag
-fno-monomorphism-restriction.


Thomas

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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-17 Thread Ben Rudiak-Gould

Frederik Eaton wrote:

I think this is a good idea. I like the inline "<-", or maybe
something like "@".


The operator-section notation (<- expr) has the big advantage of being 
unlikely to collide with any other syntax proposals.



I'm not sure what you intend to do about nested "do" statements,
though. If they correspond to different monads, I might want to have a
'borrow' in the inner "do" statement create a lifted expression in the
outer "do" statement.


In such cases you almost certainly wouldn't want to use this notation 
anyway. It's confusing enough with a single monad.


As an experiment I tried rewriting some monadic code from one of my projects 
(Reform) using the (<- expr) syntax. It was interesting. Some points:


  * Most of my uses of <- could be replaced with the inline form. In
some cases it seemed like a bad idea, because the intermediate
variable name was useful as documentation. In the other cases I'd
obviously chosen a meaningless intermediate variable name just to
get around the lack of a feature like this one.

  * I found myself writing "do return" a lot, which isn't a combination
you usually see in Haskell code. It felt odd, but perhaps you'd get
used to it.

  * The new syntax is really nice as a replacement for the annoyingly
common "x <- foo ; case x of..." idiom that I've always disliked.

  * The increased similarity to programming in an eager language was
startling at times. I'm just not used to thinking eagerly when I
write Haskell, even though I do it all the time in other languages.

  * There are tricky corner cases. For example,

  x <- getByte
  if x < 128
then return x
else return (x - 128) * 256 + (<- getByte)

doesn't do what it's probably intended to do: the second byte will
be read even if x < 128. You have to write "else do return"
instead of "else return". I'm afraid this would be easy to get
wrong. It wouldn't be hard to make the translation assume an
implicit do at the branches of if and case statements, but this
wouldn't always be what you'd want. Even worse is that short-
circuiting && and || don't work as they do in eager languages.

So on reflection I'm not sure I think this proposal is a good idea. I 
probably wouldn't be able to write or read code in this style without doing 
manual desugaring in my head, which takes away much of the appeal. But it 
might be worth adding if people can be trusted to use it judiciously.


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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-17 Thread Ben Rudiak-Gould

Bjorn Lisper wrote:

However, there is a way to resolve the ambiguity that can be claimed to be
the most natural one, and that is to always choose the "least possible"
lifting. In the example above, this would mean to interpret [[1]]++[[2]]
precisely as [[1]]++[[2]] (lift 0 levels) rather than [[1]++[2]] (lift 1
level).


It's not the mathematics I'm worried about, it's the people. Consider the 
"time flies like an arrow; fruit flies like a banana" example. What's 
interesting about it is not just the existence of more than one parse, but 
the fact that it's hard to even notice the other parses exist unless you're 
looking for them, because people are so good at unconsciously resolving this 
kind of ambiguity from context.


I'm afraid that once people get used to the idea that they can write
xs `op` ys and get implicit lifting, they will write xs ++ ys and never 
notice that it has an unlifted interpretation which will take precedence. 
This isn't the nastiest class of bug, but it's pretty nasty.


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


Re[4]: [Haskell] Mixing monadic and non-monadic functions

2005-09-16 Thread Bulat Ziganshin
Hello Udo,

Friday, September 16, 2005, 7:19:49 PM, you wrote:

>> do x <- newIORef 0
>>y <- newIORef 0
>>z <- newIORef 0
>>z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
>> writeIORef z (x'+y') }

US> May I humbly suggest you explain what problem you are actually trying to
US> solve here?  I've never felt the need to hide monadic binding behind
US> fancy syntax, defining some combinator was always sufficient.  I mean...
US> if you want C, you know where to find it.  If possible I'd rather not
US> see the same programming "style" in Haskell.

you absolutely true - i need sometimes C and don't think to use it
just to write several lines, such as when i need to compute CRC of
data stream

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: Re[2]: [Haskell] Mixing monadic and non-monadic functions

2005-09-16 Thread Udo Stenzel
Bulat Ziganshin wrote:
> i strongly support this suggestion. actually, i suggest the same for
> dealing with references (IORef/MVar/...), for example:
> 
> do x <- newIORef 0
>y <- newIORef 0
>z <- newIORef 0
>z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
> writeIORef z (x'+y') }

May I humbly suggest you explain what problem you are actually trying to
solve here?  I've never felt the need to hide monadic binding behind
fancy syntax, defining some combinator was always sufficient.  I mean...
if you want C, you know where to find it.  If possible I'd rather not
see the same programming "style" in Haskell.


Udo.
-- 
 There's too much blood in my caffeine system.


signature.asc
Description: Digital signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re[2]: [Haskell] Mixing monadic and non-monadic functions

2005-09-16 Thread Bulat Ziganshin
Hello Wolfgang,

Friday, September 16, 2005, 5:55:52 PM, you wrote:
WJ> strong argument against these proposals.  One thing I like about Haskell is
WJ> that side-effects are strictly separated from evaluation so that there is 
no 
WJ> such thing like an implicit evaluation order.

like in assembler? ;)



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re[2]: [Haskell] Mixing monadic and non-monadic functions

2005-09-16 Thread Bulat Ziganshin
Hello Sergey,

Friday, September 16, 2005, 4:02:49 PM, you wrote:

>>z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
>> writeIORef z (x'+y') }

SZ> I might be misunderstanding, but aren't we going to introduce evaluation
SZ> order for `+' in this case?

of course. really, in many situations evaluation order is just not
matter, including all IORef usage i could imagine

btw, if someone interested, explicit operation for dereferencing
variables used in ML (afair, it called just "."), and in some old
system programming language, may be BLISS

of course, automatic dereferncing could be much better, but it rises
some potential double-readings just like auto-lifting (f.e., "z:=x" -
is z must have type "IORef a" or "IORef (IORef a)", if x have type
"IORef a" ? )


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-16 Thread Wolfgang Jeltsch
Am Freitag, 16. September 2005 14:02 schrieb Sergey Zaharchenko:
> [...]

> > do x <- newIORef 0
> >y <- newIORef 0
> >z <- newIORef 0
> >z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef
> > y; writeIORef z (x'+y') }
>
> I might be misunderstanding, but aren't we going to introduce evaluation
> order for `+' in this case?

I think so and I think this is the case also for the approaches of including 
monadic expressions into "ordinary" expressions.  That is, in my opinion, a 
strong argument against these proposals.  One thing I like about Haskell is 
that side-effects are strictly separated from evaluation so that there is no 
such thing like an implicit evaluation order.

Best wishes,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-16 Thread Sergey Zaharchenko
Hello Bulat!

Thu, Sep 15, 2005 at 09:19:41PM +0400 you wrote:

> Hello Ben,
> 
> Wednesday, September 14, 2005, 6:32:27 PM, you wrote:
> 
> BRG>  do { ... ; ... borrow E ... ; ... }
> 
> BRG> is transformed into
> 
> BRG>  do { ... ; x <- E ; ... x ... ; ... }
> 
> i strongly support this suggestion. actually, i suggest the same for
> dealing with references (IORef/MVar/...), for example:
> 
> do x <- newIORef 0
>y <- newIORef 0
>z <- newIORef 0
>z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
> writeIORef z (x'+y') }

I might be misunderstanding, but aren't we going to introduce evaluation
order for `+' in this case?

-- 
DoubleF
No virus detected in this message. Ehrm, wait a minute...
/kernel: pid 56921 (antivirus), uid 32000: exited on signal 9
Oh yes, no virus:)


pgpmhxEZZ5KRt.pgp
Description: PGP signature
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-15 Thread Frederik Eaton
> I have another proposal, though. Introduce a new keyword, which I'll
> call "borrow" (the opposite of "return"), that behaves like a
> function of type (Monad m) => m a -> a inside of do statements. More
> precisely, a do expression of the form
> 
>  do { ... ; ... borrow E ... ; ... }
> 
> is transformed into
> 
>  do { ... ; x <- E ; ... x ... ; ... }
>
> where x is a fresh variable. If more than one borrow form appears in
> the same do statement, they are pulled out from left to right, which
> matches the convention already used in liftM2, ap, mapM, etc.

I think this is a good idea. I like the inline "<-", or maybe
something like "@".

I'm not sure what you intend to do about nested "do" statements,
though. If they correspond to different monads, I might want to have a
'borrow' in the inner "do" statement create a lifted expression in the
outer "do" statement. Furthermore, I might want to have a lifted
expression in the outer "do" create something which needs to be
evaluated again in the monad of the inner "do" to produce the final
value.

In any case, it would certainly be good to have better support for
lifting; and something which doesn't weaken the type system is likely
to be implemented before something that does is, so I am in favor of
investigation along the lines of your proposal.

Frederik

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-15 Thread Einar Karttunen
On 15.09 23:40, Bulat Ziganshin wrote:
> of course
> 
> class Ref c a where
>   new :: a -> IO (c a)
>   get :: c a -> IO a
>   set :: c a -> a -> IO ()

Maybe even:

class Ref m t where
  new :: a -> m (t a)
  get :: t a -> m a
  set :: t a -> a -> m ()

Or if you want to support things like FastMutInts

class Ref m t v where
  new :: v -> m t
  get :: t -> v -> m a
  set :: t -> v -> m ()

That would even support an evil IOArray instance:

instance Ref IO (IOArray Int v, Int) v where
  new iv= newArray_ (0,iv)
  get (arr,idx) = readArray arr idx
  set (arr,idx) val = writeArray arr idx val

- Einar Karttunen
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-15 Thread robert dockins

I raise you:

class (Monad m) => Ref m c | c -> m
  where new  :: a -> m (c a)
get  :: c a -> m a
peek :: c a -> m a
set  :: c a -> a -> m ()
modify   :: c a -> (a -> a) -> m a
modify_  :: c a -> (a -> a) -> m ()
modifyM  :: c a -> (a -> m a) -> m a
modifyM_ :: c a -> (a -> m a) -> m ()



Bulat Ziganshin wrote:


Hello Lyle,

Thursday, September 15, 2005, 10:50:30 PM, you wrote:



 z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
writeIORef z (x'+y') }



LK> Right, I realize my suggestion is the same as Ben's.  I just prefer a 
LK> more succinct notation, like special brackets instead of a keyword.  I 
LK> like your idea about IORefs.  I think it should work as well for 
LK> STRefs... perhaps it needs to belong to a type class, in a way?


of course

class Ref c a where
  new :: a -> IO (c a)
  get :: c a -> IO a
  set :: c a -> a -> IO ()





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


Re[2]: [Haskell] Mixing monadic and non-monadic functions

2005-09-15 Thread Bulat Ziganshin
Hello Lyle,

Thursday, September 15, 2005, 10:50:30 PM, you wrote:

>>   z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
>> writeIORef z (x'+y') }
>>
LK> Right, I realize my suggestion is the same as Ben's.  I just prefer a 
LK> more succinct notation, like special brackets instead of a keyword.  I 
LK> like your idea about IORefs.  I think it should work as well for 
LK> STRefs... perhaps it needs to belong to a type class, in a way?

of course

class Ref c a where
  new :: a -> IO (c a)
  get :: c a -> IO a
  set :: c a -> a -> IO ()



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-15 Thread Lyle Kopnicky

Bulat Ziganshin wrote:


Hello Ben,

Wednesday, September 14, 2005, 6:32:27 PM, you wrote:

BRG>  do { ... ; ... borrow E ... ; ... }

BRG> is transformed into

BRG>  do { ... ; x <- E ; ... x ... ; ... }

i strongly support this suggestion. actually, i suggest the same for
dealing with references (IORef/MVar/...), for example:

do x <- newIORef 0
  y <- newIORef 0
  z <- newIORef 0
  z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
writeIORef z (x'+y') }

 

Right, I realize my suggestion is the same as Ben's.  I just prefer a 
more succinct notation, like special brackets instead of a keyword.  I 
like your idea about IORefs.  I think it should work as well for 
STRefs... perhaps it needs to belong to a type class, in a way?


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


Re[2]: [Haskell] Mixing monadic and non-monadic functions

2005-09-15 Thread Bulat Ziganshin
Hello Ben,

Wednesday, September 14, 2005, 6:32:27 PM, you wrote:

BRG>  do { ... ; ... borrow E ... ; ... }

BRG> is transformed into

BRG>  do { ... ; x <- E ; ... x ... ; ... }

i strongly support this suggestion. actually, i suggest the same for
dealing with references (IORef/MVar/...), for example:

do x <- newIORef 0
   y <- newIORef 0
   z <- newIORef 0
   z := *x + *y   -- translated to { x' <- readIORef x; y' <- readIORef y; 
writeIORef z (x'+y') }



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-14 Thread Bjorn Lisper
Ben Rudiak-Gould:
>Frederik Eaton wrote:
>> I want the type system to be able to do "automatic lifting" of monads,
>> i.e., since [] is a monad, I should be able to write the following:
>> 
>> [1,2]+[3,4]
>> 
>> and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".
>
>The main problem is ambiguity: [[1]]++[[2]] could be [[1],[2]] or [[1,2]], 
>for example. If your proposal resolves this ambiguity in favor of one result 
>or the other, then I'm opposed to it -- it's far too easy in practice to 
>write code like this, expecting it to be lifted, and failing to notice that 
>it also has an interpretation without lifting (or the other way around). 
>This is the Perl FWIM disease[1] -- not that I dislike Perl, but people are 
>quite rightly leery about bringing this sort of thing into Haskell.

However, there is a way to resolve the ambiguity that can be claimed to be
the most natural one, and that is to always choose the "least possible"
lifting. In the example above, this would mean to interpret [[1]]++[[2]]
precisely as [[1]]++[[2]] (lift 0 levels) rather than [[1]++[2]] (lift 1
level). This is akin to choosing the most general type in the pure
Hindley-Milner type system, and it has the advantage that expressions that
are typable in the original type system, without lifting, retain their
semantics in the type system with lifting added.

Lifting (mainly of arithmetic operators) has been around for a long time in
array- and data parallel languages such as Fortran 90 and *lisp.  The kind
of ambiguity mentioned here was first observed for nested data-parallel
languages like NESL, which use nested sequences as parallel data structures.

Now, whether to include this kind of lifting in Haskell or not is an
entirely different story. One complication would be to handle possible
clashes between lifting and overloading through the class system. IMHO, I
think it would be interesting to be able to define application-specific
Haskell dialects, which can have this kind of lifting for a restricted set
of types and/or functions, whereas having it as a general feature of the
language would be quite problematic.

Björn Lisper
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-14 Thread Ben Rudiak-Gould

Frederik Eaton wrote:

I want the type system to be able to do "automatic lifting" of monads,
i.e., since [] is a monad, I should be able to write the following:

[1,2]+[3,4]

and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".


The main problem is ambiguity: [[1]]++[[2]] could be [[1],[2]] or [[1,2]], 
for example. If your proposal resolves this ambiguity in favor of one result 
or the other, then I'm opposed to it -- it's far too easy in practice to 
write code like this, expecting it to be lifted, and failing to notice that 
it also has an interpretation without lifting (or the other way around). 
This is the Perl FWIM disease[1] -- not that I dislike Perl, but people are 
quite rightly leery about bringing this sort of thing into Haskell.


I have another proposal, though. Introduce a new keyword, which I'll call 
"borrow" (the opposite of "return"), that behaves like a function of type 
(Monad m) => m a -> a inside of do statements. More precisely, a do 
expression of the form


do { ... ; ... borrow E ... ; ... }

is transformed into

do { ... ; x <- E ; ... x ... ; ... }

where x is a fresh variable. If more than one borrow form appears in the 
same do statement, they are pulled out from left to right, which matches the 
convention already used in liftM2, ap, mapM, etc.


Pros:

+ Pure sugar; no tricky interactions with the type system.

+ Nice symmetry between putting a value in a monad and taking it out.

+ Potentially helpful for beginners who ask "how do I get a String
  from an IO String?"

Cons:

- Needs a new keyword.

- Pretends to be an expression but really isn't; perhaps
  distinctive syntax would be better. (Inline "<-"?)

- Depends on enclosing do keyword: in particular, do { stmt } would
  no longer be equivalent to stmt, if stmt contains "borrow".
  Potential confusion.

- Potentially misleading for beginners (but then so is do notation,
  and the keyword "class", and n+k patterns, and so on...)

-- Ben

[1] http://www.dcs.gla.ac.uk/~partain/haskerl/partain-1.html
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Frederik Eaton
Anyway, if the idea is to ultimately wrap every value in an expression
like ([1,2]+[3,4]) in a 'run' application, that doesn't sound very
useful. Program structure might be improved, but it would be bloated
out by these calls. Also, I don't know what would happen to the
readability of type checker errors.

I think it would be more useful if the compiler took care of this
automatically. I think it would be worthwhile just for making
imperative code more readable.

Frederik

P.S. By the way, did you misunderstand what I meant by 'automatic
lifting'? Note that I'm talking about "lift" as in 'liftM', not 'lift'
from MonadTrans.

On Fri, Sep 09, 2005 at 01:17:57PM -0700, Frederik Eaton wrote:
> On Thu, Sep 08, 2005 at 09:34:33AM +0100, Keean Schupke wrote:
> > Can't you do automatic lifting with a "Runnable" class:
> > 
> > class Runnable x y where
> >run :: x -> y
> > 
> > instance Runnable (m a) (m a) where
> > run = id
> > 
> > instance Runnable (s -> m a) (s -> m a) where
> > run = id
> >  instance (Monad m,Monad n,MonadT t m,Runnable (m a) (n a)) => Runnable 
> > (t m a) (n a) where
> > run = run . down
> 
> Interesting...
> 
> > instance (Monad m,MonadT t m,Monad (t m)) => Runnable (t m a) (m a) 
> > where
> > run = down
> 
> The above is redundant, right?
> 
> > Where:
> > 
> > class (Monad m,Monad (t m)) => MonadT t m where
> >up :: m a -> t m a
> >down :: t m a -> m a
> > 
> > For example for StateT:
> > ...
> 
> So, 'run' is more like a form of casting than running, right?
> 
> How do I use it to add two lists? Where do the 'run' applications go? 
> Do you have an explicit example?
> 
> I was trying to test things out, and I'm running into problems with
> the type system, for instance when I declare:
> 
> class Cast x y where
> cast :: x -> y
> 
> instance Monad m => Cast x (m x) where
> cast = return
> 
> p1 :: (Monad m, Num a) => m (a -> a -> a)
> p1 = cast (+)
> 
> it says:
> 
> Could not deduce (Cast (a1 -> a1 -> a1) (m (a -> a -> a)))
>   from the context (Monad m, Num a)
>   arising from use of `cast' at runnable1.hs:14:5-8
> 
> But this should match the instance I declared, I don't understand what
> the problem is.
> 
> Frederik
> 
> -- 
> http://ofb.net/~frederik/
> 

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Frederik Eaton
On Thu, Sep 08, 2005 at 09:34:33AM +0100, Keean Schupke wrote:
> Can't you do automatic lifting with a "Runnable" class:
> 
> class Runnable x y where
>run :: x -> y
> 
> instance Runnable (m a) (m a) where
> run = id
> 
> instance Runnable (s -> m a) (s -> m a) where
> run = id
>  instance (Monad m,Monad n,MonadT t m,Runnable (m a) (n a)) => Runnable 
> (t m a) (n a) where
> run = run . down

Interesting...

> instance (Monad m,MonadT t m,Monad (t m)) => Runnable (t m a) (m a) where
> run = down

The above is redundant, right?

> Where:
> 
> class (Monad m,Monad (t m)) => MonadT t m where
>up :: m a -> t m a
>down :: t m a -> m a
> 
> For example for StateT:
> ...

So, 'run' is more like a form of casting than running, right?

How do I use it to add two lists? Where do the 'run' applications go? 
Do you have an explicit example?

I was trying to test things out, and I'm running into problems with
the type system, for instance when I declare:

class Cast x y where
cast :: x -> y

instance Monad m => Cast x (m x) where
cast = return

p1 :: (Monad m, Num a) => m (a -> a -> a)
p1 = cast (+)

it says:

Could not deduce (Cast (a1 -> a1 -> a1) (m (a -> a -> a)))
  from the context (Monad m, Num a)
  arising from use of `cast' at runnable1.hs:14:5-8

But this should match the instance I declared, I don't understand what
the problem is.

Frederik

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread J. Garrett Morris
On 9/9/05, Keean Schupke <[EMAIL PROTECTED]> wrote:
> Just noticed the 1+[1,2] case...  I am not certain whether this is
> possible - it is outside the
> scope of the formal definiton of Haskell and may rely on implementation
> details of the compiler/interpreter.

While this is outside the scope of the current Num class, if we adopt
the suggestion to redefine the standard classes using functional
dependencies (which is, I think, a useful addition to the standard
prelude anyway), we have, for example:

class Plus a b c | a b -> c
 where (+) :: a -> b -> c

instance (Plus a b c, Functor f) => a -> f b -> f c
 where a + fb = fmap (a +) fb

and so forth.  However, this doesn't generalize obviously (in any way
that I see) to generic two argument functions, which seemed to be what
Frederik wanted.

 /g
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Keean Schupke

Keean Schupke wrote:


I'm not sure exactly what you have in mind. Obviously I want something
that applies to all functions, with any number of arguments, and not
just (+). Furthermore, it should handle cases like 1+[2,3] where only
one value is monadic.


Just noticed the 1+[1,2] case...  I am not certain whether this is 
possible - it is outside the
scope of the formal definiton of Haskell and may rely on implementation 
details of the compiler/interpreter.


Effectivly we need to redefine list as a class, then (Num a) can be made 
an instance of the class... See my implementation of Joy in the HList 
library. (this lifts numbers into an AST rather than a list) - this 
however uses type level programming and has problems with non static 
types (IE you need to use existentials for lists who's values is not 
known at compile time)...


The easy answer is to define a type that contains both singletons and 
lists... although the type constructors may not look as neat.


   Regards,
   Keean.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Keean Schupke

Malcolm Wallace wrote:


Wolfgang Jeltsch <[EMAIL PROTECTED]> writes:

 


I'm not sure exactly what you have in mind. Obviously I want something
that applies to all functions, with any number of arguments, and not
just (+). Furthermore, it should handle cases like 1+[2,3] where only
one value is monadic.
 


I doubt that it is a good thing to extend the language in a way that such
far  reaching declarations are automatically generated.
   



I agree.  The original request was for something like
   [1,2] + [3,4]
to be automatically lifted into a monad.  But surely it is not too
difficult to define the required behaviour precisely (and only)
where needed, e.g.

   (+.) = liftM2 (+)

   [1,2] +. [3,4]

 

Why not make the monad an instance of Num, then you do not proliferate 
meaningless
similar symbols... besides which I am sure all the good ones are used in 
libraries already

(like +. <+> etc) ;)

instance (Monad m, Show a) => Show (m a)
  ...
instance (Monad m, Ord a) => Ord (m a)
  ...
instance (Monad m, Num a,Show (m a),Ord (m a)) -> Num (m a) where
   (+) = liftM2 (+)

The instances for Show and Ord can be empty if you don't need the 
functionality...


   Regards,
   Keean.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Malcolm Wallace
Wolfgang Jeltsch <[EMAIL PROTECTED]> writes:

> > I'm not sure exactly what you have in mind. Obviously I want something
> > that applies to all functions, with any number of arguments, and not
> > just (+). Furthermore, it should handle cases like 1+[2,3] where only
> > one value is monadic.
> 
> I doubt that it is a good thing to extend the language in a way that such
> far  reaching declarations are automatically generated.

I agree.  The original request was for something like
[1,2] + [3,4]
to be automatically lifted into a monad.  But surely it is not too
difficult to define the required behaviour precisely (and only)
where needed, e.g.

(+.) = liftM2 (+)

[1,2] +. [3,4]

Where the functions in question are not infix, you don't even need to
define a new name, just use (liftM fn) directly inline!

Regards,
  Malcolm
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Wolfgang Jeltsch
Am Donnerstag, 8. September 2005 22:30 schrieb Frederik Eaton:
> Hi Chad,
>
> I'm not sure exactly what you have in mind. Obviously I want something
> that applies to all functions, with any number of arguments, and not
> just (+). Furthermore, it should handle cases like 1+[2,3] where only
> one value is monadic. Keean Schupke's suggestion sounds more likely to
> be useful, but I'm still reading it. In any case, a minimum of
> syntactic overhead is desired.
>
> Frederik

Hello,

I doubt that it is a good thing to extend the language in a way that such far 
reaching declarations are automatically generated.  I would like to have more 
control about which things are declared and which are not and also in which 
way the are declared.  In addition, I'm against giving a specific class 
(Monad) a very special position among all classes.

One of the advantages of functional programming languages is that the language 
directly supports very little features but is so powerful that you can define 
new features by using the language.  Maybe, it would be good that those 
people who want this automatic lifting of functions implement it using 
Template Haskell.

Best regards,
Wolfgang
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread John Meacham
On Thu, Sep 08, 2005 at 01:30:51PM -0700, Frederik Eaton wrote:
> On Thu, Sep 08, 2005 at 09:30:34AM -0700, Scherrer, Chad wrote:
> > One of Mark Jones's articles suggests something like
> > 
> > class Plus a b c | a b -> c where
> >   (+) :: a -> b -> c
> > 
> > Would
> > 
> > instance (Plus a b c, Monad m) => Plus (m a) (m b) (m c) where
> >   mx + my = do x <- mx
> >y <- my
> >return (x + y)
> > 
> > do what you're looking for?
> 
> Hi Chad,
> 
> I'm not sure exactly what you have in mind. Obviously I want something
> that applies to all functions, with any number of arguments, and not
> just (+). Furthermore, it should handle cases like 1+[2,3] where only
> one value is monadic. Keean Schupke's suggestion sounds more likely to
> be useful, but I'm still reading it. In any case, a minimum of
> syntactic overhead is desired.

I think what he means is that if we had a somewhat better design of the
prelude type classes, we would be able to do this in haskell now for
most interesting operations. as we could write an instance like

instance (Monad m,Num a) => Num (m a) where
..
..

of course, we can't do this because Num has Ord and Show as superclasses
when it really doesn't need to. (we would have to create a separate
class for 'pattern matchable nums' if we got rid of those, but that is
no problem other than being non-haskell-98 compatable). Solving this
'class inflexibility' problem in general is something I have given some
thought too. I will let everyone know if I figure something out...

John 

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Frederik Eaton
On Thu, Sep 08, 2005 at 09:30:34AM -0700, Scherrer, Chad wrote:
> One of Mark Jones's articles suggests something like
> 
> class Plus a b c | a b -> c where
>   (+) :: a -> b -> c
> 
> Would
> 
> instance (Plus a b c, Monad m) => Plus (m a) (m b) (m c) where
>   mx + my = do x <- mx
>y <- my
>return (x + y)
> 
> do what you're looking for?

Hi Chad,

I'm not sure exactly what you have in mind. Obviously I want something
that applies to all functions, with any number of arguments, and not
just (+). Furthermore, it should handle cases like 1+[2,3] where only
one value is monadic. Keean Schupke's suggestion sounds more likely to
be useful, but I'm still reading it. In any case, a minimum of
syntactic overhead is desired.

Frederik

> --
> Original message:
> 
> Hi,
> 
> Sean's comment (yeah, it was like a billion years ago, just catching
> up) is something that I've often thought myself. 
> 
> I want the type system to be able to do "automatic lifting" of monads,
> i.e., since [] is a monad, I should be able to write the following:
> 
> [1,2]+[3,4]
> 
> and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".
> 
> Also, I would have
> 
> Reader (+1) + Reader (+4) == Reader (\x -> 2*x+5)
> 
> The point I want to make is that this is much more general than IO or
> monads! I think we all understand intuitively what mathematicians mean
> when they add two sets
> 
> {1,2}+{3,4}  (i.e. { x+y | x\in {1,2}, y\in {3,4}})
> 
> or when they add functions 
> 
> (f+g)(x) where f(x)=x+1 and g(x)=x+4
> 
> So "automatic lifting" is a feature which is very simple to describe,
> but which gives both of these notations their intuitive mathematical
> meaning - not to mention making monadic code much tidier (who wants to
> spend their time naming variables which are only used once?). I think
> it deserves more attention.
> 
> I agree that in its simplest incarnation, there is some ugliness: the
> order in which the values in the arguments are extracted from their
> monads could be said to be arbitrary. Personally, I do not think that
> this in itself is a reason to reject the concept. Because of currying,
> the order of function arguments is already important in Haskell. If
> you think of the proposed operation not as lifting, but as inserting
> `ap`s:
> 
> return f `ap` x1 `ap` ... `ap` xn
> 
> then the ordering problem doesn't seem like such a big deal. I mean,
> what other order does one expect, than one in which the arguments are
> read in the same order that 'f' is applied to them?
> 
> Although it is true that in most of the instances where this feature
> would be used, the order in which arguments are read from their monads
> will not matter; yet that does not change the fact that in cases where
> order *does* matter it's pretty damn easy to figure out what it will
> be. For instance, in
> 
> print ("a: " ++ readLn ++ "\nb: " ++ readLn)
> 
> two lines are read and then printed. Does anybody for a moment
> question what order the lines should be read in?
> 
> Frederik
> 
> 

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Scherrer, Chad
One of Mark Jones's articles suggests something like

class Plus a b c | a b -> c where
  (+) :: a -> b -> c

Would

instance (Plus a b c, Monad m) => Plus (m a) (m b) (m c) where
  mx + my = do x <- mx
   y <- my
   return (x + y)

do what you're looking for?

Chad Scherrer
Computational Mathematics Group
Pacific Northwest National Laboratory

"Time flies like an arrow; fruit flies like a banana." -- Groucho Marx

--
Original message:

Hi,

Sean's comment (yeah, it was like a billion years ago, just catching
up) is something that I've often thought myself. 

I want the type system to be able to do "automatic lifting" of monads,
i.e., since [] is a monad, I should be able to write the following:

[1,2]+[3,4]

and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".

Also, I would have

Reader (+1) + Reader (+4) == Reader (\x -> 2*x+5)

The point I want to make is that this is much more general than IO or
monads! I think we all understand intuitively what mathematicians mean
when they add two sets

{1,2}+{3,4}  (i.e. { x+y | x\in {1,2}, y\in {3,4}})

or when they add functions 

(f+g)(x) where f(x)=x+1 and g(x)=x+4

So "automatic lifting" is a feature which is very simple to describe,
but which gives both of these notations their intuitive mathematical
meaning - not to mention making monadic code much tidier (who wants to
spend their time naming variables which are only used once?). I think
it deserves more attention.

I agree that in its simplest incarnation, there is some ugliness: the
order in which the values in the arguments are extracted from their
monads could be said to be arbitrary. Personally, I do not think that
this in itself is a reason to reject the concept. Because of currying,
the order of function arguments is already important in Haskell. If
you think of the proposed operation not as lifting, but as inserting
`ap`s:

return f `ap` x1 `ap` ... `ap` xn

then the ordering problem doesn't seem like such a big deal. I mean,
what other order does one expect, than one in which the arguments are
read in the same order that 'f' is applied to them?

Although it is true that in most of the instances where this feature
would be used, the order in which arguments are read from their monads
will not matter; yet that does not change the fact that in cases where
order *does* matter it's pretty damn easy to figure out what it will
be. For instance, in

print ("a: " ++ readLn ++ "\nb: " ++ readLn)

two lines are read and then printed. Does anybody for a moment
question what order the lines should be read in?

Frederik


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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Frederik Eaton
On Thu, Sep 08, 2005 at 10:35:49AM +0200, Wolfgang Lux wrote:
> Frederik Eaton wrote:
> 
> >I want the type system to be able to do "automatic lifting" of monads,
> >i.e., since [] is a monad, I should be able to write the following:
> >and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".
> 
> Are you sure that this is the interpretation you have in mind? The
> expression do {a<-[1,2]; b<-[3,4]; return (a+b)} does *not* compute the
> element-wise sum of the two lists, but returns the list [4,5,5,6]. To
> me, this would be a very counter intuitive result for an expression
> [1,2]+[3,4].

Thanks for bringing up a good point. Yes, this is what I have in mind.

As I see it, the monadic interface for lists gives them the semantics
of (multi)sets. Adding two sets could only be interpreted as I have
said.

If you were adding, say, arrays, elementwise, the monad would be more
like a reader monad, which I also gave an example of, with the
parameter being the array index.

Furthermore, it's hard to see how one would elegantly flesh out the
semantics you propose for lists. What if the two lists have different
lengths? Thus I think set semantics is more appropriate for a list
monad.

Frederik

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Wolfgang Lux

Frederik Eaton wrote:


I want the type system to be able to do "automatic lifting" of monads,
i.e., since [] is a monad, I should be able to write the following:



and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".


Are you sure that this is the interpretation you have in mind? The
expression do {a<-[1,2]; b<-[3,4]; return (a+b)} does *not* compute the
element-wise sum of the two lists, but returns the list [4,5,5,6]. To
me, this would be a very counter intuitive result for an expression
[1,2]+[3,4].

Wolfgang

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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Keean Schupke

Can't you do automatic lifting with a "Runnable" class:

   class Runnable x y where
  run :: x -> y

   instance Runnable (m a) (m a) where
   run = id

   instance Runnable (s -> m a) (s -> m a) where
   run = id
 
   instance (Monad m,Monad n,MonadT t m,Runnable (m a) (n a)) => 
Runnable (t m a) (n a) where

   run = run . down

   instance (Monad m,MonadT t m,Monad (t m)) => Runnable (t m a) (m a) 
where

   run = down

Where:

   class (Monad m,Monad (t m)) => MonadT t m where
  up :: m a -> t m a
  down :: t m a -> m a

For example for StateT:

   downST :: Monad m => StateT st m a -> (st -> m a)
   downST m = \st -> do
   (_,a) <- runST m st
   return a

   downST' :: Monad m => (b -> StateT st m a) -> (st -> b -> m a)
   downST' m = \st b -> do
   (_,a) <- runST (m b) st
   return a


   instance (MonadState st (StateT st m),Monad m,Monad n,Runnable (st 
-> m s) (st -> n s)) => Runnable (StateT st m s) (st -> n s) 
where

   run = run . downST

   instance (MonadState st (StateT st m),Monad m) => Runnable (StateT 
st m s) (st -> m s) where

   run = downST

Keean.

 


Frederik Eaton wrote:


Hi,

Sean's comment (yeah, it was like a billion years ago, just catching
up) is something that I've often thought myself. 


I want the type system to be able to do "automatic lifting" of monads,
i.e., since [] is a monad, I should be able to write the following:

[1,2]+[3,4]

and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".

Also, I would have

Reader (+1) + Reader (+4) == Reader (\x -> 2*x+5)

The point I want to make is that this is much more general than IO or
monads! I think we all understand intuitively what mathematicians mean
when they add two sets

{1,2}+{3,4}  (i.e. { x+y | x\in {1,2}, y\in {3,4}})

or when they add functions 


(f+g)(x) where f(x)=x+1 and g(x)=x+4

So "automatic lifting" is a feature which is very simple to describe,
but which gives both of these notations their intuitive mathematical
meaning - not to mention making monadic code much tidier (who wants to
spend their time naming variables which are only used once?). I think
it deserves more attention.

I agree that in its simplest incarnation, there is some ugliness: the
order in which the values in the arguments are extracted from their
monads could be said to be arbitrary. Personally, I do not think that
this in itself is a reason to reject the concept. Because of currying,
the order of function arguments is already important in Haskell. If
you think of the proposed operation not as lifting, but as inserting
`ap`s:

return f `ap` x1 `ap` ... `ap` xn

then the ordering problem doesn't seem like such a big deal. I mean,
what other order does one expect, than one in which the arguments are
read in the same order that 'f' is applied to them?

Although it is true that in most of the instances where this feature
would be used, the order in which arguments are read from their monads
will not matter; yet that does not change the fact that in cases where
order *does* matter it's pretty damn easy to figure out what it will
be. For instance, in

print ("a: " ++ readLn ++ "\nb: " ++ readLn)

two lines are read and then printed. Does anybody for a moment
question what order the lines should be read in?

Frederik



On Tue, Mar 23, 2004 at 12:55:56PM -0500, Sean E. Russell wrote:
 


On Tuesday 23 March 2004 11:36, Graham Klyne wrote:
   


I think you're a rather stuck with the "temporary variables" (which they're
not really), but it might be possible to hide some of the untidiness in an
auxiliary monadic function.
 


That seems to be the common suggestion: write my own visitors.

I'm just surprised that there isn't a more elegant mechanism for getting 
interoperability between monadic and non-monadic functions.  The current 
state of affairs just seems awkward.  


[Warning: quasi-rant]

Caveat: I'm not smart enough, and I don't know enough, to criticize Haskell, 
so please don't misconstrue my comments.  To quote Einstein: "When I'm asking 
simple questions and I'm getting simple answers, I'm talking to God."  I 
simply mistrust, and therefore question, systems where simple things are 
overly involved.


The standard explaination about why monads are so troublesome always sounds 
like an excuse to me.  We have monads, because they allow side-effects.  Ok.  
If programs that used side effects were uncommon, I'd be fine with them being 
troublesome -- but they aren't.  Maybe it is just me, but my Haskell programs 
invariably develop a need for side effects within a few tens of lines of 
code, whether IO, Maybe, or whatnot.  And I can't help but think that 
language support to make dealing with monads easier -- that is, to integrate 
monads with the rest of the language, so as to alleviate the need for 
constant lifting -- would be a Good Thing.


Hmmm.  Could I say that Haskell requires "heavy lifting"?

--
### SER   
##

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Jeremy Gibbons
On Wed, 7 Sep 2005, Frederik Eaton wrote:

> I want the type system to be able to do "automatic lifting" of monads,
> i.e., since [] is a monad, I should be able to write the following:
>
> [1,2]+[3,4]
>
> and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".

You might want to take a look at "Monadification of Functional Programs"
by Erwig and Ren (Science of Computer Programming, 52:101-129, 2004):

  http://web.engr.oregonstate.edu/~erwig/papers/abstracts.html

which describes the transformation that introduces such a monadic
structure.

Jeremy

[EMAIL PROTECTED]
  Oxford University Computing Laboratory,TEL: +44 1865 283508
  Wolfson Building, Parks Road,  FAX: +44 1865 273839
  Oxford OX1 3QD, UK.
  URL: http://www.comlab.ox.ac.uk/oucl/people/jeremy.gibbons.html


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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Frederik Eaton
I guess what I don't understand is what's wrong with the first
alternative you mention:

> One way of preventing the compiler from rearranging effects is to
> thread though a dummy variable - like a "World token", ala the IO
> monad - which makes the order of operations explicit as an extra
> data dependency, then compile the resulting code.

which sounds sort of the same as the semantics I'm envisioning.

Frederik

On Wed, Sep 07, 2005 at 11:41:41PM -0700, Frederik Eaton wrote:
> > Frederik,
> > To do "automatic lifting" you need to do a (higher-order) effect analysis, 
> > then make sure the 
> > compiler doesn't rearrange applications which have conflicting effects.
> 
> Hrm, I disagree. I don't think this is what I was advocating in my
> message.
> 
> What I'm advocating is a reasonably simple modification of the type
> checker to allow a more concise syntax. Unless I'm misunderstanding
> you, there is no special "effect analysis" needed.
> 
> I haven't worked it out exactly, but what you'd do is the following:
> 
> 1. keep track of when you are unifying types within a "monadic
>context"; for instance when you unify "Monad m => x -> m b" with
>"Monad m => y -> m b", you have to unify "x" and "y". this second
>unification of "x" and "y" will be done within a "context" to which
>the monad "m" has been added, to make a note of the fact that
>computations in "m" within "x" or "y" can be lifted.
> 
> 2. if two types don't unify, but you can get them to unify by
>inserting a lift operation from one of the current context monads,
>then do that. e.g. when you find an application where a function
>expects an argument of type "a" and the user is passing something
>of type "m a", and "m" is in the context (so we know that we can
>eventually get rid of it), then do the application with `ap`
>instead of "$".
> 
> I don't pretend that this is rigorous, but I do hope it gives a better
> idea of what I'm talking about doing. The point of the last few
> paragraphs of my message was to argue that even with this syntax
> change, users will still be able to easily reason about the
> side-effects of monadic parts of their code. Do you disagree with that
> assertion? Or are you just saying that the syntax change as I propose
> it is called "effect analysis"?
> 
> Frederik
> 
> -- 
> http://ofb.net/~frederik/
> ___
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-07 Thread Frederik Eaton
> Frederik,
> To do "automatic lifting" you need to do a (higher-order) effect analysis, 
> then make sure the 
> compiler doesn't rearrange applications which have conflicting effects.

Hrm, I disagree. I don't think this is what I was advocating in my
message.

What I'm advocating is a reasonably simple modification of the type
checker to allow a more concise syntax. Unless I'm misunderstanding
you, there is no special "effect analysis" needed.

I haven't worked it out exactly, but what you'd do is the following:

1. keep track of when you are unifying types within a "monadic
   context"; for instance when you unify "Monad m => x -> m b" with
   "Monad m => y -> m b", you have to unify "x" and "y". this second
   unification of "x" and "y" will be done within a "context" to which
   the monad "m" has been added, to make a note of the fact that
   computations in "m" within "x" or "y" can be lifted.

2. if two types don't unify, but you can get them to unify by
   inserting a lift operation from one of the current context monads,
   then do that. e.g. when you find an application where a function
   expects an argument of type "a" and the user is passing something
   of type "m a", and "m" is in the context (so we know that we can
   eventually get rid of it), then do the application with `ap`
   instead of "$".

I don't pretend that this is rigorous, but I do hope it gives a better
idea of what I'm talking about doing. The point of the last few
paragraphs of my message was to argue that even with this syntax
change, users will still be able to easily reason about the
side-effects of monadic parts of their code. Do you disagree with that
assertion? Or are you just saying that the syntax change as I propose
it is called "effect analysis"?

Frederik

-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-07 Thread Ben Lippmeier

Frederik Eaton wrote:


I want the type system to be able to do "automatic lifting" of monads,
i.e., since [] is a monad, I should be able to write the following:

[1,2]+[3,4]

and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".



print ("a: " ++ readLn ++ "\nb: " ++ readLn)

two lines are read and then printed. Does anybody for a moment
question what order the lines should be read in?



Frederik,
To do "automatic lifting" you need to do a (higher-order) effect 
analysis, then make sure the compiler doesn't rearrange applications 
which have conflicting effects.


One way of preventing the compiler from rearranging effects is to thread 
though a dummy variable - like a "World token", ala the IO monad - which 
makes the order of operations explicit as an extra data dependency, then 
compile the resulting code.


Another way is to use the effect information to lift the applications 
into a hierarchy of monads which represent how effectful the application 
is, then compile the monadic code directly. There's a paper by Andrew 
Tolmach called "Optimizing ML using a hierarchy of monadic types", which 
does exactly this.


Tolmach's approach worked ok, but there were some problems with higher 
order functions.. ie with map :: (a -E> b) -> [a] -E> [b] where E is 
some effect, you have to assume a worst case effect for the first 
argument - so any expression using map can't be moved around by the 
compiler - eg for the full laziniess transform.


Another way would be just to annotate every application with the effects 
it has, then have the compiler check these before it tries to rearrange 
anything - and have an extra rule that you can't suspend an application 
which has visible effects.


I am working on a compiler for my PhD project which takes this third 
option. I've got the effect analysis working, but I had to resort to a 
graph based type inference method - which is something that wouldn't be 
easilly added to something like GHC.


Onward!
Ben.




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


Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-07 Thread Frederik Eaton
Hi,

Sean's comment (yeah, it was like a billion years ago, just catching
up) is something that I've often thought myself. 

I want the type system to be able to do "automatic lifting" of monads,
i.e., since [] is a monad, I should be able to write the following:

[1,2]+[3,4]

and have it interpreted as "do {a<-[1,2]; b<-[3,4]; return (a+b)}".

Also, I would have

Reader (+1) + Reader (+4) == Reader (\x -> 2*x+5)

The point I want to make is that this is much more general than IO or
monads! I think we all understand intuitively what mathematicians mean
when they add two sets

{1,2}+{3,4}  (i.e. { x+y | x\in {1,2}, y\in {3,4}})

or when they add functions 

(f+g)(x) where f(x)=x+1 and g(x)=x+4

So "automatic lifting" is a feature which is very simple to describe,
but which gives both of these notations their intuitive mathematical
meaning - not to mention making monadic code much tidier (who wants to
spend their time naming variables which are only used once?). I think
it deserves more attention.

I agree that in its simplest incarnation, there is some ugliness: the
order in which the values in the arguments are extracted from their
monads could be said to be arbitrary. Personally, I do not think that
this in itself is a reason to reject the concept. Because of currying,
the order of function arguments is already important in Haskell. If
you think of the proposed operation not as lifting, but as inserting
`ap`s:

return f `ap` x1 `ap` ... `ap` xn

then the ordering problem doesn't seem like such a big deal. I mean,
what other order does one expect, than one in which the arguments are
read in the same order that 'f' is applied to them?

Although it is true that in most of the instances where this feature
would be used, the order in which arguments are read from their monads
will not matter; yet that does not change the fact that in cases where
order *does* matter it's pretty damn easy to figure out what it will
be. For instance, in

print ("a: " ++ readLn ++ "\nb: " ++ readLn)

two lines are read and then printed. Does anybody for a moment
question what order the lines should be read in?

Frederik



On Tue, Mar 23, 2004 at 12:55:56PM -0500, Sean E. Russell wrote:
> On Tuesday 23 March 2004 11:36, Graham Klyne wrote:
> > I think you're a rather stuck with the "temporary variables" (which they're
> > not really), but it might be possible to hide some of the untidiness in an
> > auxiliary monadic function.
> 
> That seems to be the common suggestion: write my own visitors.
> 
> I'm just surprised that there isn't a more elegant mechanism for getting 
> interoperability between monadic and non-monadic functions.  The current 
> state of affairs just seems awkward.  
> 
> [Warning: quasi-rant]
> 
> Caveat: I'm not smart enough, and I don't know enough, to criticize Haskell, 
> so please don't misconstrue my comments.  To quote Einstein: "When I'm asking 
> simple questions and I'm getting simple answers, I'm talking to God."  I 
> simply mistrust, and therefore question, systems where simple things are 
> overly involved.
> 
> The standard explaination about why monads are so troublesome always sounds 
> like an excuse to me.  We have monads, because they allow side-effects.  Ok.  
> If programs that used side effects were uncommon, I'd be fine with them being 
> troublesome -- but they aren't.  Maybe it is just me, but my Haskell programs 
> invariably develop a need for side effects within a few tens of lines of 
> code, whether IO, Maybe, or whatnot.  And I can't help but think that 
> language support to make dealing with monads easier -- that is, to integrate 
> monads with the rest of the language, so as to alleviate the need for 
> constant lifting -- would be a Good Thing.
> 
> Hmmm.  Could I say that Haskell requires "heavy lifting"?
> 
> -- 
> ### SER   
> ### Deutsch|Esperanto|Francaise|Linux|XML|Java|Ruby|Aikido
> ### http://www.germane-software.com/~ser  jabber.com:ser  ICQ:83578737 
> ### GPG: http://www.germane-software.com/~ser/Security/ser_public.gpg



> ___
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell


-- 
http://ofb.net/~frederik/
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-24 Thread Glynn Clements

[EMAIL PROTECTED] wrote:

> >> We'd all love to make the lifting implicit, but no one knows how to 
> >> do it
> >> without breaking the whole language.
> >
> > I've heard people talk about the functional "purity" of Haskell -- 
> > you'd have
> > to break this purity to add implicit lifting?
> 
> I don't think you would break the functional purity of Haskell if you 
> did such a thing, but you'd probably need some new syntax to help out 
> the type system.  Perhaps something like:
> 
>  assertBool "fail" $ length () == length ()
> 
> So here, () performs the same function as the <- operator, but 
> assigns the result to an "anonymous variable" and is instantly consumed 
> by whatever function uses its value.  Please don't berate me for my 
> choice of syntax, by the way: that was just an example :).
> 
> One problem with this is that you now don't know what order those two 
> operations take place: does "somefunc a" run first, or does "somefunc 
> b" run first?  You have this same problem in other imperative languages 
> too; I'm not sure if, e.g. C defines an order for function evaluation 
> to occur.

C doesn't define the order in which function arguments are evaluated,
so:

foo(getchar(), getchar());

could be equivalent to either:

a = getchar();
b = getchar();
foo(a, b);
or:
a = getchar();
b = getchar();
foo(b, a);

This isn't restricted to I/O, but affects any operation which has side
effects, e.g.

foo(++x, ++x);

This is *why* I/O actions aren't treated as functions in pure
functional languages.

Regarding the "solution" of using liftM (liftM2 etc): these impose a
left-to-right evaluation order, e.g.:

liftM2   :: (Monad m) => (a -> b -> c) -> (m a -> m b -> m c)
liftM2 f  = \a b -> do { a' <- a; b' <- b; return (f a' b') }

One consequence of this is that, even if (==) is an equivalence
relation, "liftM2 (==)" may not be, as the order of the arguments is
significant.

More generally, lifted functions may have semantics which differ
greatly from the underlying function. Personally, I'm quite happy that
Haskell doesn't allow this to be hidden by implicit lifting.

-- 
Glynn Clements <[EMAIL PROTECTED]>
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Max Kirillov
On Tue, Mar 23, 2004 at 10:29:26AM -0500, Sean E. Russell wrote:
> Here's my base case:
> 
>   someFunc :: String -> IO [a]
>   ...
>   ax <- someFunc a
>   bx <- someFunc b
>   assertBool "fail" $ length ax == length bx
>
> <...>What I'd much rather have is:
> 
>   ...
>   assertBool "fail" $ (length $ someFunc a) == (length $ someFunc b)
> 
> which is more readable, to my eye.

Monads are not just a fascistic typing feture. They are to ensure the
order of actions. Your first version makes clear (and makes sure)
that 'someFunc a' is executed before 'someFunc b'. The second does not.

If you don't need that, maybe you should inspect why your someFunc has
type '.. -> IO ..'. Usually that means that it involves some IO, so
you may not ignore the order of actions.

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


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread ozone
On 24/03/2004, at 9:54 AM, Sean E. Russell wrote:

We'd all love to make the lifting implicit, but no one knows how to 
do it
without breaking the whole language.
I've heard people talk about the functional "purity" of Haskell -- 
you'd have
to break this purity to add implicit lifting?
I don't think you would break the functional purity of Haskell if you 
did such a thing, but you'd probably need some new syntax to help out 
the type system.  Perhaps something like:

assertBool "fail" $ length () == length ()

So here, () performs the same function as the <- operator, but 
assigns the result to an "anonymous variable" and is instantly consumed 
by whatever function uses its value.  Please don't berate me for my 
choice of syntax, by the way: that was just an example :).

One problem with this is that you now don't know what order those two 
operations take place: does "somefunc a" run first, or does "somefunc 
b" run first?  You have this same problem in other imperative languages 
too; I'm not sure if, e.g. C defines an order for function evaluation 
to occur.  Perhaps you could just dictate a left-to-right order, or 
maybe come up with bizarre (<1 ... >) and (<2 ... >) constructs to 
indicate what order things should run in.  Some ideas to get started, 
anyway.

I do agree with you that not having syntactic sugar to do something 
like that is somewhat inconvenient, and it would be a nice addition to 
the language.

A related problem which was discussed here recently is Haskell's lack 
of
per-type namespaces, something which even C programmers take for 
granted.
Again, the problem is the tricky interaction with type inference.
Augh!  Yes!  I've hit that as well.  Well, in my case, it was 
constructors.  I
was trying to do:

data Effort = Easy | Middle | Hard
data Impact = Low | Middle | High
Perhaps one option for this would be to have explicitly quantified data 
namespaces, so that you would have to write 'Effort.Middle' to 
construct something of type Effort, and 'Impact.Middle' to construct 
something of type Impact.

The problems you mention of in Haskell are certainly solvable: it's 
just the mere matter of implementing such features ... :)  I think the 
Haskell community (at least, the community who are capable of making 
such changes to the Haskell implementations) is unfortunately a bit too 
small to put such syntactic niceties in the language; we simply don't 
have enough human resources to do it.  But I'm sure plenty of others 
would agree that those features would be nice!

--
% Andre Pang : trust.in.love.to.save
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Duncan Coutts
On Tue, 2004-03-23 at 15:29, Sean E. Russell wrote:

> Here's my base case:
> 
>   someFunc :: String -> IO [a]
>   ...
>   ax <- someFunc a
>   bx <- someFunc b
>   assertBool "fail" $ length ax == length bx
> 
> I don't like the assignments; the typing is redundant, if I have a lot of 
> asserts like this, and the "variables" are temporary.  What I'd much rather 
> have is:
> 
>   ...
>   assertBool "fail" $ (length $ someFunc a) == (length $ someFunc b)
> 
> which is more readable, to my eye.
> 
> The only solution which has been suggested that may work is liberal use of the 
> liftM variants, but this gets *really* tedious and obtuse.
> 
> Is there an elegant way to do what I want to do, or am I stuck with 
> procedural-style assignments and bunches of temp vars?

For a project I did which involved a lot of monadic code I used some
combinators which allow you to write in a more applicative/functional
style but still thread the monad state through everything.

Basically instead of writing:

do
  a' <- foo a
  b' <- foo b
  c' <- foo c
  return $ f a' b' c'

you write:
f $> foo a <$> foo b <$> foo c

Unfortunately it doesn't work so well with infix operators, you'd have
to say (==) $> firstThing <$> secondThing
which is not quite so appealing.

Your example would look like so:
assertBool "fail" <$$> (==) $> (length $> someFunc a) <$> (length $> someFunc b)

Here's the little combinator library, it's really just a matter of using
infix versions of standard monad functions and playing with their
left/right associativity and precedence.

import Monad (liftM, ap)

infixl 1  $>, <$>   --same as liftM & ap, but left associative infix
infixr 0  <$$>  --same as =<<, but different precedence

($>) :: Monad m => (a -> b) -> (m a -> m b)
($>) = liftM

(<$>) :: Monad m => m (a -> b) -> (m a -> m b)
(<$>) = ap

(<$$>) :: Monad m => (a -> m b) -> (m a -> m b)
(<$$>) = (=<<)

--
Duncan

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


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Sean E. Russell
On Tuesday 23 March 2004 17:04, you wrote:
>   * Memory management (allocation and deallocation) is effortless.
>
>   * Creating lexical closures is very easy.
>
>   * You don't have to declare the types of all your functions and local
> bindings, because the implementation can figure them out for itself.
>
>   * You don't have to ensure that values are computed before they're used,
> because the implementation handles that too.
>
> If you were learning C instead of Haskell, you'd be complaining (and
> rightly so) about the effort required to do these things in C.

Actually, most of these things are pretty easy in Ruby, too.  Everything is 
easy in Ruby :-)  But what I like about Haskell is stuff like pattern 
matching and list comprehension.  I also particularly like the effortless 
strong typing.  Before Haskell, I thought strong typing meant variable type 
declarations, which are tedious.

When I find myself doing design and writing pseudocode, and having it look a 
lot like a language I use, I decide that the language is Good.  So far, this 
has happened to me with both Haskell and Ruby -- Haskell at a higher level, 
when I'm thinking about functions that I'll need, Ruby when I'm sketching out 
algorithms.  In eight years of coding Java professionally, I *never* found 
myself writing any pseudo-code that looked anything like Java.

> We'd all love to make the lifting implicit, but no one knows how to do it
> without breaking the whole language.

I've heard people talk about the functional "purity" of Haskell -- you'd have 
to break this purity to add implicit lifting?

> A related problem which was discussed here recently is Haskell's lack of
> per-type namespaces, something which even C programmers take for granted.
> Again, the problem is the tricky interaction with type inference.

Augh!  Yes!  I've hit that as well.  Well, in my case, it was constructors.  I 
was trying to do:

data Effort = Easy | Middle | Hard
data Impact = Low | Middle | High

Effort and Impact aren't related (in any useful ontological sense that I can 
think of), so I don't want to make them instance of the same type -- but I 
can't reuse Middle without it (AFAIK).  So I had to fudge, and call the 
Impact constructor "Medium", which sort of grates, as you can imagine.

Yeah, that's something I'd like a work-around for, too.

> Unless/until these problems are resolved, all you can do is learn a bunch
> of different languages and use the one which is most convenient for a
> particular task. Haskell, for all its problems, is a strong contender for
> many tasks.

What I use Haskell for are those tasks where I really want something compiled.  
What surprised me, after I'd used it for a few weeks, was that my 
applications were more robust than I expected, given the novelty of the 
language to me.  If I were to write any software (in a language that I know) 
upon which lives depended, it'd be in Haskell.

I find that, with Ruby, I don't struggle -- the code just flows -- but I 
*liberally* use unit testing, and even so I spend a fair amount of time 
debugging .  With Haskell, I spend some effort figuring out how to solve the 
problem and some time getting it to compile, but once it does, it generally 
works as expected.  Very rarely do I need to debug code that compiles.  With 
Java, I spend a fair amount of time getting stuff compiled and running, and 
then even more time debugging, and then more time fixing stuff later.  

The most amazing thing to me about Java is how little the compilation phase 
contributes to making code more robust.  My Ruby is no more buggy than my 
Java, and it is loosely typed and entirely interpreted.  In fact, I generally 
trust Java applications less than Ruby applications.

But, I fear I'm wandering off-topic.  Thanks to everybody for the feedback 
about my problem; I have a working solution using the visitor pattern, and 
while I'm still concerned about IO monads (yes, just IO; other monads -- such 
as Maybe -- are less troublesome), it is "good enough".

-- 
### SER   
### Deutsch|Esperanto|Francaise|Linux|XML|Java|Ruby|Aikido
### http://www.germane-software.com/~ser  jabber.com:ser  ICQ:83578737 
### GPG: http://www.germane-software.com/~ser/Security/ser_public.gpg
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Ben Rudiak-Gould
On Tue, 23 Mar 2004, Sean E. Russell wrote:

> The standard explaination about why monads are so troublesome always sounds 
> like an excuse to me.  We have monads, because they allow side-effects.  Ok.  
> If programs that used side effects were uncommon, I'd be fine with them being 
> troublesome -- but they aren't.  Maybe it is just me, but my Haskell programs 
> invariably develop a need for side effects within a few tens of lines of 
> code, whether IO, Maybe, or whatnot.  And I can't help but think that 
> language support to make dealing with monads easier -- that is, to integrate 
> monads with the rest of the language, so as to alleviate the need for 
> constant lifting -- would be a Good Thing.

I agree with this, but the support you describe is difficult to add.

Programming languages differ not so much in what they make possible as in
what they make easy. In Haskell (to pick just a few examples):

  * Memory management (allocation and deallocation) is effortless.

  * Creating lexical closures is very easy.

  * You don't have to declare the types of all your functions and local
bindings, because the implementation can figure them out for itself.

  * You don't have to ensure that values are computed before they're used,
because the implementation handles that too.

If you were learning C instead of Haskell, you'd be complaining (and
rightly so) about the effort required to do these things in C.

Unfortunately, no one has figured out how to make everything easy at the
same time, and the problem you've run into is an example of this. The
monad I/O model exists because of implicit data dependencies (the last
bullet point above); the "heavy lifting" exists because of type inference.
We'd all love to make the lifting implicit, but no one knows how to do it
without breaking the whole language.

A related problem which was discussed here recently is Haskell's lack of
per-type namespaces, something which even C programmers take for granted.
Again, the problem is the tricky interaction with type inference.

Unless/until these problems are resolved, all you can do is learn a bunch
of different languages and use the one which is most convenient for a
particular task. Haskell, for all its problems, is a strong contender for
many tasks.


-- Ben

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


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Graham Klyne
At 12:55 23/03/04 -0500, Sean E. Russell wrote:
On Tuesday 23 March 2004 11:36, Graham Klyne wrote:
> I think you're a rather stuck with the "temporary variables" (which they'=
re
> not really), but it might be possible to hide some of the untidiness in an
> auxiliary monadic function.
That seems to be the common suggestion: write my own visitors.

I'm just surprised that there isn't a more elegant mechanism for getting=20
interoperability between monadic and non-monadic functions.  The current=20
state of affairs just seems awkward. =20
[Warning: quasi-rant]

Caveat: I'm not smart enough, and I don't know enough, to criticize Haskell=
,=20
so please don't misconstrue my comments.  To quote Einstein: "When I'm aski=
ng=20
simple questions and I'm getting simple answers, I'm talking to God."  I=20
simply mistrust, and therefore question, systems where simple things are=20
overly involved.
The standard explaination about why monads are so troublesome always sounds=
=20
like an excuse to me.  We have monads, because they allow side-effects.  Ok=
=2E =20
If programs that used side effects were uncommon, I'd be fine with them bei=
ng=20
troublesome -- but they aren't.  Maybe it is just me, but my Haskell progra=
ms=20
invariably develop a need for side effects within a few tens of lines of=20
code, whether IO, Maybe, or whatnot.  And I can't help but think that=20
language support to make dealing with monads easier -- that is, to integrat=
e=20
monads with the rest of the language, so as to alleviate the need for=20
constant lifting -- would be a Good Thing.
I'd make one further point in response... I don't think the "heavy lifting" 
here is because of Monads in general:  some Monads (Maybe, lists, etc) mix 
very easily with pure functional code.  I think it's the IO Monad in 
particular:  here you are creating interactions between two fundamentally 
different environments:  the real-world, which is fundamentally stateful 
and non-referentially-transparent, and mathematical functions that are 
quite the opposite.

Hmmm.  Could I say that Haskell requires "heavy lifting"?
:-)

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Iavor S. Diatchki
hi,
at some level you are right that some more syntactic sugar
and stuff could make monads more atracitve. for the time
being here is how i'd write what you want bellow:
f # m   = liftM f m
mx === my  = liftM2 (==) m1 m2
assertBool "fail" $ (length # someFunc a) === (length # someFunc b)

at the moment we only have syntactic sugar for working with the list monad
(list comprehensions etc), and environemnt (aka reader) monad (implicit 
parameters).

hope this helps
-iavor
Sean E. Russell wrote:

Hello,

I posted this question to comp.lang.functional, and someone suggested that I 
try this group instead.

I'm struggling with monads.  Well, not monads themselves, but mixing them with 
non-monadic functions.

Here's my base case:

someFunc :: String -> IO [a]
...
ax <- someFunc a
bx <- someFunc b
assertBool "fail" $ length ax == length bx
I don't like the assignments; the typing is redundant, if I have a lot of 
asserts like this, and the "variables" are temporary.  What I'd much rather 
have is:

...
assertBool "fail" $ (length $ someFunc a) == (length $ someFunc b)
which is more readable, to my eye.

The only solution which has been suggested that may work is liberal use of the 
liftM variants, but this gets *really* tedious and obtuse.

Is there an elegant way to do what I want to do, or am I stuck with 
procedural-style assignments and bunches of temp vars?

Thanks!

 

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


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Sean E. Russell
On Tuesday 23 March 2004 11:36, Graham Klyne wrote:
> I think you're a rather stuck with the "temporary variables" (which they're
> not really), but it might be possible to hide some of the untidiness in an
> auxiliary monadic function.

That seems to be the common suggestion: write my own visitors.

I'm just surprised that there isn't a more elegant mechanism for getting 
interoperability between monadic and non-monadic functions.  The current 
state of affairs just seems awkward.  

[Warning: quasi-rant]

Caveat: I'm not smart enough, and I don't know enough, to criticize Haskell, 
so please don't misconstrue my comments.  To quote Einstein: "When I'm asking 
simple questions and I'm getting simple answers, I'm talking to God."  I 
simply mistrust, and therefore question, systems where simple things are 
overly involved.

The standard explaination about why monads are so troublesome always sounds 
like an excuse to me.  We have monads, because they allow side-effects.  Ok.  
If programs that used side effects were uncommon, I'd be fine with them being 
troublesome -- but they aren't.  Maybe it is just me, but my Haskell programs 
invariably develop a need for side effects within a few tens of lines of 
code, whether IO, Maybe, or whatnot.  And I can't help but think that 
language support to make dealing with monads easier -- that is, to integrate 
monads with the rest of the language, so as to alleviate the need for 
constant lifting -- would be a Good Thing.

Hmmm.  Could I say that Haskell requires "heavy lifting"?

-- 
### SER   
### Deutsch|Esperanto|Francaise|Linux|XML|Java|Ruby|Aikido
### http://www.germane-software.com/~ser  jabber.com:ser  ICQ:83578737 
### GPG: http://www.germane-software.com/~ser/Security/ser_public.gpg


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


Re: [Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Graham Klyne
I think you're a rather stuck with the "temporary variables" (which they're 
not really), but it might be possible to hide some of the untidiness in an 
auxiliary monadic function.

Assuming this function is given:

assertBool :: String -> Bool -> IO ()

...

My first stab would be:

assertBool1 :: IO [a] -> IO [a] -> ([a] -> [a] -> Bool) -> IO ()
assertBool1 f1 f2 comp = do
a1 <- f1
a2 <- f2
assertBool "fail" $ comp a1 a2
Then your main code could be:

assertBool1 (someFunc a) (someFunc b) (==)

...

So far so good, maybe?  But what happens if the values you want to test are 
not lists?  The assertBool1 could be generalized somewhat:

assertBool2 :: IO a -> IO b -> (a -> b -> Bool) -> IO ()
assertBool2 fa fb comp = do
va <- fa
vb <- fb
assertBool "fail" $ comp va vb
(All that's really changed here is the type signature)

...

But what if you want a test that uses just one value, or three, or 
more?  At this point I think you start having to use the liftM variants, 
but others may have better ideas.  It may be that the lifting can be hidden 
in auxiliiarty function/operator definitions;  e.g. see the Haskell library 
function Monad.ap for possible clues.

...

Anyway, here's some complete code, tested under Hugs:
[[
import Monad( unless )
assertBool :: String -> Bool -> IO ()
assertBool err bool = unless bool (error err)
someFunc :: String -> IO String
someFunc s = return s
assertBool1 :: IO [a] -> IO [a] -> ([a] -> [a] -> Bool) -> IO ()
assertBool1 f1 f2 comp = do
a1 <- f1
a2 <- f2
assertBool "fail" $ comp a1 a2
test1 :: String -> String -> IO ()
test1 a b =
do  { assertBool1 (someFunc a) (someFunc b) (==)
; putStrLn "test1 OK"
}
-- test1 "a" "a" -> "test1 OK"
-- test1 "a" "b" -> "fail"
assertBool2 :: IO a -> IO b -> (a -> b -> Bool) -> IO ()
assertBool2 fa fb comp = do
va <- fa
vb <- fb
assertBool "fail" $ comp va vb
test2 :: String -> String -> IO ()
test2 a b =
do  { assertBool1 (someFunc a) (someFunc b) (==)
; putStrLn "test2 OK"
}
-- test2 "a" "a" -> "test2 OK"
-- test2 "a" "b" -> "fail"
]]
#g
--
At 10:29 23/03/04 -0500, Sean E. Russell wrote:
Hello,

I posted this question to comp.lang.functional, and someone suggested that I
try this group instead.
I'm struggling with monads.  Well, not monads themselves, but mixing them 
with
non-monadic functions.

Here's my base case:

someFunc :: String -> IO [a]
...
ax <- someFunc a
bx <- someFunc b
assertBool "fail" $ length ax == length bx
I don't like the assignments; the typing is redundant, if I have a lot of
asserts like this, and the "variables" are temporary.  What I'd much rather
have is:
...
assertBool "fail" $ (length $ someFunc a) == (length $ 
someFunc b)

which is more readable, to my eye.

The only solution which has been suggested that may work is liberal use of 
the
liftM variants, but this gets *really* tedious and obtuse.

Is there an elegant way to do what I want to do, or am I stuck with
procedural-style assignments and bunches of temp vars?
Thanks!

--
### SER
### Deutsch|Esperanto|Francaise|Linux|XML|Java|Ruby|Aikido
### http://www.germane-software.com/~ser  jabber.com:ser  ICQ:83578737
### GPG: http://www.germane-software.com/~ser/Security/ser_public.gpg
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Mixing monadic and non-monadic functions

2004-03-23 Thread Sean E. Russell
Hello,

I posted this question to comp.lang.functional, and someone suggested that I 
try this group instead.

I'm struggling with monads.  Well, not monads themselves, but mixing them with 
non-monadic functions.

Here's my base case:

someFunc :: String -> IO [a]
...
ax <- someFunc a
bx <- someFunc b
assertBool "fail" $ length ax == length bx

I don't like the assignments; the typing is redundant, if I have a lot of 
asserts like this, and the "variables" are temporary.  What I'd much rather 
have is:

...
assertBool "fail" $ (length $ someFunc a) == (length $ someFunc b)

which is more readable, to my eye.

The only solution which has been suggested that may work is liberal use of the 
liftM variants, but this gets *really* tedious and obtuse.

Is there an elegant way to do what I want to do, or am I stuck with 
procedural-style assignments and bunches of temp vars?

Thanks!

-- 
### SER   
### Deutsch|Esperanto|Francaise|Linux|XML|Java|Ruby|Aikido
### http://www.germane-software.com/~ser  jabber.com:ser  ICQ:83578737 
### GPG: http://www.germane-software.com/~ser/Security/ser_public.gpg
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell