[Haskell-cafe] Yet Another Forkable Class
suhorng Y
suhorng at gmail.com
Thu Aug 22 17:32:47 CEST 2013
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 <agocorona at gmail.com>
> 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 <oleg at okmij.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
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Alberto.
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130822/a6c3d334/attachment.htm>
More information about the Haskell-Cafe
mailing list