[Haskell-cafe] Yet Another Forkable Class

76 views
Skip to first unread message

John ExFalso

unread,
Aug 21, 2013, 6:42:12 PM8/21/13
to haskel...@haskell.org
TLDR: New forkable monad/transformer suggestion http://pastebin.com/QNUVL12v (hpaste is down)

Hi,

There are a dozen packages on hackage defining a class for monads that can be forked, however none of these are modular enough to be useful in my opinion.

In particular the following are not addressed:
1. Cases when the child thread's monad is different from the parent's
2. Monad transformers (this is somewhat addressed with Control.Monad.Trans.Control)

I will try to demonstrate both issues with an example.

1. WebSockets

WebSockets is a monad that cannot itself be forked. This is because at any given time there should only be a single thread listening on a websocket.
However there is a reasonable monad that can be forked off, namely one that can send to the websocket - one that has access to the Sink.

So first off a "Forkable" class should not look like this:

class (MonadIO m, MonadIO n) => Forkable m where
    fork :: m () -> m ThreadId

But rather like this:

class Forkable m n where
    fork :: n () -> m ThreadId

For our example the instance would be

instance (Protocol p) => Forkable (WebSockets p) (ReaderT (Sink p) IO) where
    fork (ReaderT f) = liftIO . forkIO . f =<< getSink

Another example would be a child that should not be able to throw errors as opposed to the parent thread.

2. ReaderT

Continuing from the previous example to demonstrate the need to distinguish forkable transformers.
Say we have some shared state S that both parent and child should have access to:

type Parent p = ReaderT (TVar S) (WebSockets p)
type Child p = ReaderT (TVar S) (ReaderT (Sink p) IO)

The "forkability" of Child from Parent should be implied, however with Forkable we have to write a separate instance.

So what I suggest is a second class:

class ForkableT t where
    forkT :: (Forkable m n) => t n () -> t m ThreadId

And then:

instance ForkableT (ReaderT r) where
    forkT (ReaderT f) = ReaderT $ fork . f

We can also introduce a default for Forkable that uses a ForkableT instance:

class (MonadIO m, MonadIO n) => Forkable m n where
    fork :: n () -> m ThreadId
    default fork :: ForkableT t => t n () -> t m ThreadId
    fork = forkT

instance (Forkable m n) => Forkable (ReaderT r m) (ReaderT r n)

This means Child is automatically Forkable from Parent, no need to write a specific case for our specific monads (and if we newtype it we can use -XGeneralizedNewtypeDeriving)

Note how MonadTransControl already solves the specific problem of lifting a forking operation into ReaderT. However consider ResourceT from Control.Monad.Resource: it is basically a ReaderT, however in order to safely deallocate resources when sharing reference counting is needed. This means a simple lift would not suffice.

We can nevertheless provide a default ForkableT based on MonadTransControl:
class ForkableT t where
    forkT :: (Forkable m n) => t n () -> t m ThreadId
    default forkT :: (MonadTransControl t, Forkable m n) => t n () -> t m ThreadId
    forkT t = liftWith $ \run -> fork $ run t >> return ()

Actually resourcet's reference counting resourceForkIO also nicely demonstrates the first problem:
type Parent p = ResourceT (WebSockets p)
type Child p = ResourceT (ReaderT (Sink p) IO)

Note how we cannot use resourceForkIO without touching the underlying monads.

What do you think? Is there already an established way of modular forking? I wouldn't like to litter hackage with another unusable Forkable class:)

ol...@okmij.org

unread,
Aug 22, 2013, 1:20:04 AM8/22/13
to Haskel...@haskell.org

Perhaps effect libraries (there are several to choose from) could be a
better answer to Fork effects than monad transformers. One lesson from
the recent research in effects is that we should start thinking what
effect we want to achieve rather than which monad transformer to
use. Using ReaderT or StateT or something else is an implementation
detail. Once we know what effect to achieve we can write a handler, or
interpreter, to implement the desired operation on the World, obeying
the desired equations. And we are done.

For example, with ExtEff library with which I'm more familiar, the
Fork effect would take as an argument a computation that cannot throw
any requests. That means that the parent has to provide interpreters
for all child effects. It becomes trivially to implement:

> Another example would be a child that should not be able to throw errors as
> opposed to the parent thread.
It is possible to specify which errors will be allowed for the child
thread (the ones that the parent will be willing to reflect and
interpret). The rest of errors will be statically prohibited then.

> instance (Protocol p) => Forkable (WebSockets p) (ReaderT (Sink p) IO) where
> fork (ReaderT f) = liftIO . forkIO . f =<< getSink

This is a good illustration of too much implementation detail. Why do we
need to know of (Sink p) as a Reader layer? Would it be clearer to
define an Effect of sending to the socket? Computation's type will
make it patent the computation is sending to the socket.
The parent thread, before forking, has to provide a handler for that
effect (and the handler will probably need a socket).

Defining a new class for each effect is possible but not needed at
all. With monad transformers, a class per effect is meant to hide the
ordering of transformer layers in a monad transformer stack. Effect
libraries abstract over the implementation details out of the
box. Crutches -- extra classes -- are unnecessary. We can start by
writing handlers on a case-by-case basis. Generalization, if any,
we'll be easier to see. From my experience, generalizing from concrete
cases is easier than trying to write a (too) general code at the
outset. Way too often, as I read and saw, code that is meant to be
reusable ends up hardly usable.




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

Alberto G. Corona

unread,
Aug 22, 2013, 7:15:20 AM8/22/13
to ol...@okmij.org, haskell-cafe
The paper is very interesting:

http://www.cs.indiana.edu/~sabry/papers/exteff.pdf

It seems that the approach is mature enough and it is better in every way than monad transformers, while at the same time the syntax may become almost identical to MTL for many uses.

I only expect to see the library in Hackage with all the blessings, and with all the instances of the MTL classes in order to make the transition form monad transformers  to ExtEff as transparent as possible


2013/8/22 <ol...@okmij.org>



--
Alberto.

John ExFalso

unread,
Aug 22, 2013, 10:50:23 AM8/22/13
to Alberto G. Corona, ol...@okmij.org, haskell-cafe
To be honest I'm not so sure about these "effects"... Simply the fact that the Member class needs -XOverlappingInstances means that we cannot have duplicate or polymorphic effects. It will arbitrarily pick the first match in the former and fail to compile in the latter case.

Furthermore I don't really understand the way open sums are implemented. These unions should be disjoint, but the way they're implemented in the paper they try to be "true" unions which cannot be done as that would need type equality (-XOverlappingInstances is a hack around this)

A correct disjoint open sum would behave well with duplicate and polymorphic types in the type list. For example we should be able to project the open sum equivalent of Either String String into the second String but we cannot with the implementation in the paper. This means we need to ~index~ the type list instead of picking the result type and "trying for equality" with each entry. Something like this: http://lpaste.net/92069

Of course this is very inconvenient and simply replaces the monad transformers' lifts with a static index into the "effect" list.
In general I think there is no convenient way of stacking effects that is also type safe. At some point we have to disambiguate which effect we are trying to use one way or the other. The implementation in the paper simply picks a heuristic and chooses the first effect that seems to match and discards the others.

suhorng Y

unread,
Aug 22, 2013, 11:32:47 AM8/22/13
to haskell-cafe
For the open union used in extensible effects, apart from using the
Typeable mechanism, is there a more protected way to implement
the open sum type?

I managed to modified the Member class given in the paper, but
ended up having to use the vague OverlappingInstance. That's not
quite what I hope. I'm not even sure whether the instance `Member t (t :> r)`
is more specific than `Member t (t' :> r)`. 

--
suhorng

{-# LANGUAGE KindSignatures, TypeOperators, GADTs, FlexibleInstances, 
             FlexibleContexts, MultiParamTypeClasses, OverlappingInstances #-}
-- FlexibleContexts is for Show instance of Union

import Data.Functor
import Control.Applicative -- for several functor instances

-- open union
infixr 2 :>
data (a :: * -> *) :> b

data Union r v where
  Elsewhere :: Functor t' => Union r v -> Union (t' :> r) v
  Here :: Functor t => t v -> Union (t :> r) v

class Member t r where
  inj :: Functor t => t v -> Union r v
  prj :: Functor t => Union r v -> Maybe (t v)

instance Member t (t :> r) where
  inj tv = Here tv
  prj (Here tv)     = Just tv
  prj (Elsewhere _) = Nothing

-- Note: overlapped by letting t' = t
instance (Functor t', Member t r) => Member t (t' :> r) where
  inj tv = Elsewhere (inj tv)
  prj (Here _)      = Nothing
  prj (Elsewhere u) = prj u

decomp :: Functor t => Union (t :> r) v -> Either (Union r v) (t v)
decomp (Here tv)     = Right tv
decomp (Elsewhere u) = Left u

-- Auxiliary definitions for tests
data Void
newtype Func a = Func a

instance Show (Union Void a) where
  show _ = undefined

instance (Show (t v), Show (Union r v)) => Show (Union (t :> r) v) where
  show (Here tv)     = "Here " ++ show tv
  show (Elsewhere u) = "Elsewhere " ++ show u

instance Functor Func where
  fmap f (Func x) = Func (f x)

instance Show a => Show (Func a) where
  show (Func a) = show a

type Stk = Maybe :> Either Char :> Func :> Void
type Stk' = Either Char :> Func :> Void -- used in `deTrue`, `deFalse`

unTrue :: Union Stk Bool
unTrue = inj (Func True)

unFalse :: Union Stk Bool
unFalse = inj (Just False)

-- `Func` is repeated
un5 :: Union (Maybe :> Func :> Either Char :> Func :> Void) Int
un5 = inj (Func 5)

maybe2 :: Maybe (Func Int)
maybe2 = prj un5

maybeTrue :: Maybe (Func Bool)
maybeTrue = prj unTrue

maybeFalse1 :: Maybe (Func Bool)
maybeFalse1 = prj unFalse

maybeFalse2 :: Maybe (Maybe Bool)
maybeFalse2 = prj unFalse

deTrue :: Either (Union Stk' Bool) (Maybe Bool)
deTrue = decomp unTrue

deFalse :: Either (Union Stk' Bool) (Maybe Bool)
deFalse = decomp unFalse



2013/8/22 Alberto G. Corona <agoc...@gmail.com>

ol...@okmij.org

unread,
Aug 23, 2013, 4:06:08 AM8/23/13
to 0sl...@gmail.com, Haskel...@haskell.org

I must stress that OpenUnion1.hs described (briefly) in the paper
is only one implementation of open unions, out of many possible.
For example, I have two more implementations. A year-old version of
the code implemented open unions *WITHOUT* overlapping instances or
Typeable.
http://okmij.org/ftp/Haskell/extensible/TList.hs

The implementation in the paper is essentially the one described in
the full HList paper, Appendix C. The one difference is that the HList
version precluded duplicate summands. Adding the duplication check to
OpenUnion1 takes three lines of code. I didn't add them because it
didn't seem necessary, or even desired.

I should further stress, OverlappingInstances are enabled only
within one module, OpenUnion1.hs. The latter is an internal, closed
module, not meant to be modified by a user. No user program needs to
declare OverlappingInstances in its LANGUAGES pragma. Second,
OverlappingInstances are used only within the closed type class
Member. This type class is not intended to be user-extensible; the
programmer need not and should not define any more instances for
it. The type class is meant to be closed. So Member emulates closed
type families implemented in the recent version of GHC. With the
closed type families, no overlapping instances are needed.

> Simply the fact that the Member class needs -XOverlappingInstances
> means that we cannot have duplicate or polymorphic effects. It will
> arbitrarily pick the first match in the former and fail to compile in
> the latter case.
Of course we can have duplicate layers. In that case, the dynamically closest
handler wins -- which sounds about right (think of reset in delimited
control). The file Eff.hs even has a test case for that, tdup.
BTW, I'm not sure of the word 'pick' -- the Member class is
a purely compile-time constraint. It doesn't do any picking -- it doesn't
do anything at all at run-time.

> For example we should be able to project the open sum equivalent of
> Either String String into the second String but we cannot with the
> implementation in the paper.
You inject a String or a String, and you will certainly
project a String (the one your have injected). What is the problem
then? You can always project what you have injected. Member merely
keeps track of what types could possibly be injected/projected.
So, String + String indeed should be String.


By polymorphic effects you must mean first-class polymorphism (because
the already implemented Reader effect is polymorphic in the
environment). First of all, there are workarounds. Second, I'm not
sure what would be a good example of polymorphic effect (aside from
ST-monad-like).

> To be honest I'm not so sure about these "effects"...
Haskell Symposium will have a panel on effect libraries in Haskell.
It seems plausible that effects, one way or the other, will end ip in
Haskell. Come to Haskell Symposium, tell us your doubts and
concerns. We want to hear them.

Nicolas Trangez

unread,
Aug 23, 2013, 8:29:37 AM8/23/13
to ol...@okmij.org, Haskel...@haskell.org
On Fri, 2013-08-23 at 08:06 +0000, ol...@okmij.org wrote:
> > It will
> > arbitrarily pick the first match in the former and fail to compile
> in
> > the latter case.
> Of course we can have duplicate layers. In that case, the dynamically
> closest
> handler wins -- which sounds about right (think of reset in delimited
> control).

Did anyone ever consider using type-level literals (strings) to 'name'
effects (or transformer layers when using monad stacks)?

A stupid example (OTOH) could be

updateStats :: (Member (State "min" Int) r, Member (State "max" Int)
r) => Int -> Eff r ()
updateStats i = do
min <- askMin
max <- askMax
when (i < min) $ putMin i
when (i > max) $ putMax i
where
askMin :: Member (State "min" Int) r => Eff r Int
askMin = ask
putMax :: Member (State "max" Int) r => Int -> Eff r ()
putMax = put
-- askMax, putMin accordingly

Using constraint synonyms/ConstraintKinds (e.g. type StateMax r = Member
(State "max" Int) r) might reduce some notation overhead.

Just a thought.

Nicolas

Ozgur Akgun

unread,
Aug 24, 2013, 9:45:22 AM8/24/13
to Nicolas Trangez, ol...@okmij.org, Haskell cafe
Hi.

On 23 August 2013 13:29, Nicolas Trangez <nic...@incubaid.com> wrote:
Did anyone ever consider using type-level literals (strings) to 'name'
effects (or transformer layers when using monad stacks)?

Edwin Brady had this in his effects library in Idris.

Ozgur.

Suhail Shergill

unread,
Nov 28, 2014, 4:52:15 AM11/28/14
to ol...@okmij.org, Haskel...@haskell.org
having recently taken over as maintainer for the extensible-effects library, i'm
looking to address some of the current implementation concerns. specifically:

1] the use/need for Typeable in Data.OpenUnion

ol...@okmij.org writes:

> I must stress that OpenUnion1.hs described (briefly) in the paper is only one
> implementation of open unions, out of many possible. For example, I have two
> more implementations. A year-old version of the code implemented open unions
> *WITHOUT* overlapping instances or Typeable.
> http://okmij.org/ftp/Haskell/extensible/TList.hs

how does the TList.hs implementation compare with, say, OpenUnion2.hs? neither
require OverlappingInstances, and the TList implementation also does away with
the Typeable constraint. are there reasons why it might not make sense to use
TList.hs as the only/default implementation of Data.OpenUnion?

2] scope for impredicative/first-class polymorphism

> By polymorphic effects you must mean first-class polymorphism (because the
> already implemented Reader effect is polymorphic in the environment). First of
> all, there are workarounds.

what are the "workarounds" in question?

> Second, I'm not sure what would be a good example of polymorphic effect (aside
> from ST-monad-like).

the paper mentioned "explicitly marking state, and providing an allocation
system using monadic regions". is this related to
<http://okmij.org/ftp/Haskell/regions.html#light-weight> and if so, what work
needs to be done to apply those ideas to extensible-effects?

--
Suhail

adam vogt

unread,
Nov 29, 2014, 3:30:05 PM11/29/14
to Suhail Shergill, haskell-cafe
Hi Suhail,

On Fri, Nov 28, 2014 at 4:52 AM, Suhail Shergill
<suhails...@gmail.com> wrote:
> having recently taken over as maintainer for the extensible-effects library, i'm
> looking to address some of the current implementation concerns. specifically:
>
> 1] the use/need for Typeable in Data.OpenUnion
> how does the TList.hs implementation compare with, say, OpenUnion2.hs? neither
> require OverlappingInstances, and the TList implementation also does away with
> the Typeable constraint. are there reasons why it might not make sense to use
> TList.hs as the only/default implementation of Data.OpenUnion?

You need to write an instance of TCode for every different "effect"
included in the union for the lookup to work. Check out this example
usage of TList.hs:

mkV :: Int -> ([] :> Maybe :> Void) Int
mkV 1 = H [1,2,3]
mkV 2 = T (H (Just 5))
mkV 3 = T (T (undefined :: Void Int))

-- | >>> test1
-- [Just [1,2,3],Nothing,Nothing]
test1 :: [Maybe [Int]]
test1 = map (prj . mkV) [1 .. 3]

-- | >>> test2
-- [Nothing,Just (Just 5),Nothing]
test2 :: [Maybe (Maybe Int)]
test2 = map (prj . mkV) [1 .. 3]

type instance TCode [] = Z
type instance TCode Maybe = S Z


If you instead had

type instance TCode [] = Z
type instance TCode Maybe = Z

then test2 would not typecheck, and the type error doesn't suggest (to
me) that the TCode instances are wrong.


I think you're better off depending on a

type family Eq :: Bool where
Eq x x = True
Eq x y = False

Or the equivalent with overlapping instances if the code is supposed
to work with ghc-7.6.


Another objection about TList is that it is a linked list, so
operations with types at the "end" of the union are probably
relatively slow at runtime, since you end up pattern matching on "n" T
constructors in some cases. It might be faster to have more of that
traversal done at compile time as in:

http://code.haskell.org/HList/Data/HList/Variant.hs

Or with unions that use Typeable.


I'm not sure about your other questions.

Regards,
Adam

Suhail Shergill

unread,
Dec 1, 2014, 1:14:48 AM12/1/14
to adam vogt, Suhail Shergill, haskell-cafe
adam vogt <vogt...@gmail.com> writes:

> You need to write an instance of TCode for every different "effect"
> included in the union for the lookup to work.
> ...

thanks for the explanation; the Includes instances make more sense now

> I think you're better off depending on a
>
> type family Eq :: Bool where
> Eq x x = True
> Eq x y = False
>
> Or the equivalent with overlapping instances if the code is supposed
> to work with ghc-7.6.

yes, i've updated the code on hackage to fall back on the overlapping instances
implementation for ghc-7.6

> Another objection about TList is that it is a linked list, so operations with
> types at the "end" of the union are probably relatively slow at runtime, since
> you end up pattern matching on "n" T constructors in some cases.

that may just be a limitation for the code being written for ghc-7.4 iiuc

> It might be faster to have more of that traversal done at compile time as in:
>
> http://code.haskell.org/HList/Data/HList/Variant.hs

thanks for the additional reference. i've been meaning to read up on HList;
perhaps this will be my segue

> Or with unions that use Typeable.

actually with Typeable being kind polymorphic in ghc-7.8, the improved deriving
code, -XAutoDeriveTypeable and -XStandaloneDeriving i don't see much of a
drawback with the above approach.

> I'm not sure about your other questions.

yes, they were more directed at oleg (in the cc), but figured others might have
made their way through these waters before me, so it couldn't hurt to ask.

cheers

--
Suhail

ol...@okmij.org

unread,
Dec 2, 2014, 10:31:44 AM12/2/14
to suhails...@gmail.com, Haskel...@haskell.org

First of all, thank you indeed for taking over as the maintainer of
the extensible-effects library. Thank you for sending me your
questions directly.

> 1] the use/need for Typeable in Data.OpenUnion
>
> > I must stress that OpenUnion1.hs described (briefly) in the paper is
> > only one implementation of open unions, out of many possible. For
> > example, I have two more implementations. A year-old version of the
> > code implemented open unions *WITHOUT* overlapping instances or
> > Typeable.
> > http://okmij.org/ftp/Haskell/extensible/TList.hs
>
> how does the TList.hs implementation compare with, say, OpenUnion2.hs?
> neither require OverlappingInstances, and the TList implementation
> also does away with the Typeable constraint. are there reasons why it
> might not make sense to use TList.hs as the only/default
> implementation of Data.OpenUnion?

Although TList doesn't require neither overlapping instances nor
Typeable, it is not so easy to use since one has to `register' any new
type or effects.

To show that one can indeed implement the interface of OpenUnion.hs as
it is *without* Typeable or overlapping instances, I have just written
http://okmij.org/ftp/Haskell/extensible/OpenUnion4.hs

It is meant to be a drop-in replacement for OpenUnion2.hs. At least
for my Eff code, it does indeed act that way. Nothing in the code has
to be changed save for the import declaration. On the down side, in
OpenUnion4.hs, projections and injections take linear time in the size
of the union. How much difference it really makes in practice is
unclear (since the projection and injection operations can be computed
statically). Only benchmarks could tell.

> 2] scope for impredicative/first-class polymorphism
>
> > By polymorphic effects you must mean first-class polymorphism (because
> > the already implemented Reader effect is polymorphic in the
> > environment). First of all, there are workarounds.
>
> what are the "workarounds" in question?

Well, OpenUnion4 is one workaround. Since it does not use Typeable,
there are no problems with (ST s)--like types.

> the paper mentioned "explicitly marking state, and providing an
> allocation system using monadic regions". is this related to
> <http://okmij.org/ftp/Haskell/regions.html#light-weight> and if so,
> what work needs to be done to apply those ideas to extensible-effects?

I'm afraid that the answer is `just do it'. I thought about the
implementation and jotted down some notes somewhere. There didn't seem
to be any significant problems. Alas I hadn't have the time since to
pursue this further.

Thank you!

Suhail Shergill

unread,
Dec 13, 2014, 11:11:13 PM12/13/14
to ol...@okmij.org, suhails...@gmail.com, Haskel...@haskell.org
ol...@okmij.org writes:

> First of all, thank you indeed for taking over as the maintainer of
> the extensible-effects library.

you're welcome! and thank you for the library in question to begin with; i
intend to port the ideas to scala as well.

> To show that one can indeed implement the interface of OpenUnion.hs as
> it is *without* Typeable or overlapping instances, I have just written
> http://okmij.org/ftp/Haskell/extensible/OpenUnion4.hs

thanks for the concrete code sample. also, iiuc, if i were to back-port this
code to ghc versions 7.6 and before, i should be able to do away with dependence
on closed type families replacing it with overlapping instances. correct?

if so, i'll try and expose that point in the design space as well since that
would permit us to use effects in the return type of other 'Eff's even in
systems not supporting closed type families. currently we have this for ghc-7.8
as can be seen in the contrived test here:
<https://github.com/bfops/extensible-effects/blob/master/test/Test.hs#L163>

> It is meant to be a drop-in replacement for OpenUnion2.hs. At least
> for my Eff code, it does indeed act that way. Nothing in the code has
> to be changed save for the import declaration. On the down side, in
> OpenUnion4.hs, projections and injections take linear time in the size
> of the union. How much difference it really makes in practice is
> unclear (since the projection and injection operations can be computed
> statically). Only benchmarks could tell.

agreed. i am also contemplating breaking out open unions into an independent
library.

--
Suhail

Roman Cheplyaka

unread,
Jan 2, 2015, 6:16:18 PM1/2/15
to ol...@okmij.org, suhails...@gmail.com, Haskel...@haskell.org
On 02/12/14 17:31, ol...@okmij.org wrote:
> To show that one can indeed implement the interface of OpenUnion.hs as
> it is *without* Typeable or overlapping instances, I have just written
> http://okmij.org/ftp/Haskell/extensible/OpenUnion4.hs

It is interesting to note that this is exactly the solution (to almost
the same problem) that Andres Löh and I came up with last spring:
http://bit.ly/1xgo7fQ

Roman
Reply all
Reply to author
Forward
0 new messages