[Haskell-cafe] (no subject)
Tom Ellis
tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Sun Apr 24 21:28:35 UTC 2016
On Sun, Apr 24, 2016 at 11:20:24PM +0200, Bertram Felgenhauer wrote:
> Tom Ellis wrote:
> > On Sun, Apr 24, 2016 at 08:07:40PM +0000, haskell-cafe-bounces at haskell.org wrote:
> [snip]
> > > David Feuer wrote:
> > > > What I'm looking for is more limited than lazy IO or unsafeInterleaveIO,
> > > > but it seems quite possible that there's no way to get just what I'm
> > > > looking for with the IO type proper using GHC's implementation of IO. Lazy
> > > > IO allows evaluation to drive action. When a thunk is forced, it may
> > > > trigger I/O (spooky action at a distance). What I'm talking about is
> > > > separating what actions are performed from what values are calculated from
> > > > them. Here's a partial concept which won't actually compile because of the
> > > > lazy pattern matches:
> > > >
> > > > data MyIO a = forall b . MyIO (b -> a) (IO b)
> > > > instance Functor MyIO where
> > > > fmap f ~(MyIO t m) = MyIO (f . t) m
> > > > instance Applicative MyIO where
> > > > pure a = MyIO (const a) (pure ())
> > > > MyIO t1 m1 <*> ~(MyIO t2 m2) =
> > > > MyIO (\(r1, r2) -> t1 r1 (t2 r2)) ((,) <$> m1 <*> m2)
> > > > instance Monad MyIO where
> > > > ???
> > > > instance MonadFix MyIO where
> > > > ???
> > >
> > > I believe that using this interface `unsafeInterleaveIO` could be
> > > implemented as follows, making it just as powerful as lazy IO:
> > >
> > > data Box a = Box a
> > >
> > > unsafeInterleaveMyIO :: MyIO a -> MyIO a
> > > unsafeInterleaveMyIO act = do
> > > act' <- Box `fmap` act
> > > return $ case act' of Box !r -> r
> > >
> > > Have I missed anything?
> >
> > Since MyIO and its associate functions don't contain any unsafe primitives
> > it seems highly unlikely you can implement unsafeInterleaveIO with them!
> >
> > In fact I can't see how MyIO is any different to IO. All you can do with
> > the function field is fmap it over the IO action field.
>
> Note that the code for the Monad instance is missing. The desired
> semantics as I understood them were that in `x >>= y`, `y` could access
> the "data part" that is produced by the embedded function (first
> component of MyIO) of `x` before the IO action associated with `x`
> was performed; the IO action would be triggered when that function
> forces its argument. This "early access" to the data part would then
> allow `mfix` to be lazier than it currently is.
I see. Well there is no benefit in splitting MyIO up into two parts. It
will suffice to do
data MyIO a = MyIO (IO a)
Then perhaps you want something like
instance Monad MyIO where
return = MyIO . return
~(MyIO m) >>= ~(MyIO f) = MyIO (unsafeInterleaveIO m >>= f)
> The point I'm trying to make is that these are exactly the semantics
> that `unsafeInterleaveIO` provides, and to my mind this is best
> demonstrated by implementing that function in the MyIO interface.
So your idea is that unsafeInterleaveIO can be captured as a monad?
Interesting.
Tom
More information about the Haskell-Cafe
mailing list