
On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard
I don't see why one would need session types, channels... to express that. I maybe need a more complicated coroutines (ruby) example that would require using this system.
OK, how would you type these routines in Haskell? def simple yield "hello" yield 1 yield (lambda { |x| x + 1 }) end def useSimple state = 0 result = nil simple { |x| if (state == 0) then result = x else if (state == 1) then result += (x * 4).toString else if (state == 2) then result += x.call(10).toString state = state + 1 } result end I know it's a bit contrived, but you get the idea. In Haskell using Control.Coroutine: simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: rest) rest () simple = do put "hello" put 1 put (\x -> x + 1) useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: rest) rest String useSimple = do string <- get int <- get func <- get return (string ++ show (int * 4) ++ show (func 10)) result :: String result = snd $ connects simple useSimple -- result = "hello411"

First thing I've tried when learning Ruby was something like that: ================ def a yield {puts 1} end a {yield} ================ It didn't work. Can Coroutine.hs do something like that? On 18 Dec 2008, at 13:26, Ryan Ingram wrote:
On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard
wrote: I don't see why one would need session types, channels... to express that. I maybe need a more complicated coroutines (ruby) example that would require using this system.
OK, how would you type these routines in Haskell?
def simple yield "hello" yield 1 yield (lambda { |x| x + 1 }) end
def useSimple state = 0 result = nil simple { |x| if (state == 0) then result = x else if (state == 1) then result += (x * 4).toString else if (state == 2) then result += x.call(10).toString state = state + 1 } result end
I know it's a bit contrived, but you get the idea.
In Haskell using Control.Coroutine:
simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: rest) rest () simple = do put "hello" put 1 put (\x -> x + 1)
useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: rest) rest String useSimple = do string <- get int <- get func <- get return (string ++ show (int * 4) ++ show (func 10))
result :: String result = snd $ connects simple useSimple -- result = "hello411" _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Miguel, Thursday, December 18, 2008, 1:42:21 PM, you wrote: ruby doesn't support coroutines, but only iterators (where control moved from caller to callee). usually control is on the caller side, and coroutines gives control to both (or many) sides coroutines are easily emulated in IO monad using multithreading, and i think that are easily emulated both in Ruby and Haskell using callCC
First thing I've tried when learning Ruby was something like that:
================ def a yield {puts 1} end
a {yield} ================
It didn't work. Can Coroutine.hs do something like that?
On 18 Dec 2008, at 13:26, Ryan Ingram wrote:
On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard
wrote: I don't see why one would need session types, channels... to express that. I maybe need a more complicated coroutines (ruby) example that would require using this system.
OK, how would you type these routines in Haskell?
def simple yield "hello" yield 1 yield (lambda { |x| x + 1 }) end
def useSimple state = 0 result = nil simple { |x| if (state == 0) then result = x else if (state == 1) then result += (x * 4).toString else if (state == 2) then result += x.call(10).toString state = state + 1 } result end
I know it's a bit contrived, but you get the idea.
In Haskell using Control.Coroutine:
simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: rest) rest () simple = do put "hello" put 1 put (\x -> x + 1)
useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: rest) rest String useSimple = do string <- get int <- get func <- get return (string ++ show (int * 4) ++ show (func 10))
result :: String result = snd $ connects simple useSimple -- result = "hello411" _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 2008 Dec 18, at 5:47, Bulat Ziganshin wrote:
ruby doesn't support coroutines, but only iterators (where control moved from caller to callee). usually control is on the caller side, and coroutines gives control to both (or many) sides
Right, and you don't normally do iterators in Haskell; you do map/fmap. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Hello Brandon, Thursday, December 18, 2008, 7:05:05 PM, you wrote:
ruby doesn't support coroutines, but only iterators (where control moved from caller to callee). usually control is on the caller side, and coroutines gives control to both (or many) sides
Right, and you don't normally do iterators in Haskell; you do map/fmap.
iterators are not cycles :) they allow to return value without returning control -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

In my opinion, in Haskell, you don't need coroutines because you have
lazy evaluation.
You example below is simply an example of a heterogenous list being
read. The simplest way to implement a heterogenous list in Haskell is
to use a tuple. Or you could use the HList package.
--
Robin
On Thu, 18 Dec 2008 02:26:26 -0800
"Ryan Ingram"
On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard
wrote: I don't see why one would need session types, channels... to express that. I maybe need a more complicated coroutines (ruby) example that would require using this system.
OK, how would you type these routines in Haskell?
def simple yield "hello" yield 1 yield (lambda { |x| x + 1 }) end
def useSimple state = 0 result = nil simple { |x| if (state == 0) then result = x else if (state == 1) then result += (x * 4).toString else if (state == 2) then result += x.call(10).toString state = state + 1 } result end
I know it's a bit contrived, but you get the idea.
In Haskell using Control.Coroutine:
simple :: forall rest. Session (String :!: Int :!: (Int -> Int) :!: rest) rest () simple = do put "hello" put 1 put (\x -> x + 1)
useSimple :: forall rest. Session (String :?: Int :?: (Int -> Int) :?: rest) rest String useSimple = do string <- get int <- get func <- get return (string ++ show (int * 4) ++ show (func 10))
result :: String result = snd $ connects simple useSimple -- result = "hello411" _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Dec 18, 2008 at 3:01 AM, Robin Green
In my opinion, in Haskell, you don't need coroutines because you have lazy evaluation.
That's a fair criticism. Lazy evaluation basically gives you a coroutine embedded in any data structure. But sometimes making implicit things explicit aids understanding! Especially when there can be communication in both directions; that is, the data structure can be somewhat dependent on the code doing the evaluation. In addition, I think coroutines under effectful monads are still potentially useful. It would not be too hard to extend this library to allow effectful computations to communicate. At the very least I can easily imagine a version of InSession that supports lifting from IO into coroutines.
You example below is simply an example of a heterogenous list being read. The simplest way to implement a heterogenous list in Haskell is to use a tuple. Or you could use the HList package.
Actually, the result of "runSession simple" is isomorphic to a tuple/heterogeneous list:
data instance InSession (a :!: r) v = W a (InSession r v) newtype instance InSession Eps v = Eps v
runSession simple :: InSession (String :!: Int :!: (Int -> Int) :!: Eps) () => W "hello" $ W 1 $ W (+1) $ Eps () Similarily, useSimple evaluates to a function of three arguments:
newtype instance InSession (a :?: r) v = R (a -> InSession r v)
runSession useSimple => R $ \string -> R $ \int -> R $ \func -> Eps (string ++ show (int * 4) ++ show (func 10)) There are three pieces to this package: 1) A monad-like structure that gives nice syntax for the construction of InSession values. 2) A data family that gives a representation of these values as different functors. This is similar to using the TypeCompose library [1] and the (,) a and (->) a Functor instances [2]. That is, in some way (a :!: r) represents ((,) a) . r. (.) here represents function composition at the *type* level. This allows composition of functors: (a :!: b :?: c :!: Eps) == (a,) . (b ->) . (c,) . Id == \v -> (a, b -> (c,v)) where again, the lambda is at the type level, and (a,) means a section at the type level similar to (5 <=) at the value level. (As an aside, my thanks to Simon Peyton-Jones for suggesting this representation of sessions using type families.) 3) A "duality" type family and connector which shows which functors can be connected to which other functors. This is similar to the "zap" operation in Category-extras [3]. I wrote the library initially to play around with (1); Indexed monads are an interesting topic and I don't think they are well covered outside of the dense material by Oleg & friends. I definitely understand them much better after writing it! (2) and (3) are there to give some structure to the exercise. The other goal was to give a machine-checkable proof of the semantics of session types described in Jesse Tov's paper [4]. In the paper, sessions are represented by effectful computations, which run in parallel and communicate over *untyped* channels, using unsafeCoerce. The paper contains a proof that this is indeed safe, but it seemed worthwhile to encode the proof in the Haskell type system, allowing the possibility to remove unsafeCoerce. -- ryan [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/TypeCompose-0.6.3 [2] http://haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad-Instanc... [3] http://comonad.com/reader/2008/zapping-strong-adjunctions/ [4] http://www.ccs.neu.edu/home/tov/pubs/session08.html

Robin Green wrote:
In my opinion, in Haskell, you don't need coroutines because you have lazy evaluation.
You example below is simply an example of a heterogenous list being read. The simplest way to implement a heterogenous list in Haskell is to use a tuple. Or you could use the HList package.
Not quite. The consumer, useSimple, is an example of a heterogenous list being read. The producer, simple, is an example of producing a heterogenous list, value by value, on demand. You don't get that from HList for free. The difference between coroutines and lazy evaluation is that in the latter the consumer has full control. Producer supplies all the thunks, consumer picks which thunk to evaluate. Of course the producer could return a pair of first value and the rest of the computation, but then any control structure can be encoded using continuations. The question is one of notational convenience.

On Thu, 2008-12-18 at 11:01 +0000, Robin Green wrote:
In my opinion, in Haskell, you don't need coroutines because you have lazy evaluation.
You example below is simply an example of a heterogenous list being read. The simplest way to implement a heterogenous list in Haskell is to use a tuple. Or you could use the HList package.
Lazy evaluation obviates some, but certainly not all uses of coroutines.
participants (7)
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Derek Elkins
-
Mario Blazevic
-
Miguel Mitrofanov
-
Robin Green
-
Ryan Ingram