[Haskell-cafe] Re: Why is type 'b' forced to be type 'm a' and not possibly 'm a -> m a' (Anatoly Zaretsky)

Vivian McPhail vivian.mcphail at paradise.net.nz
Mon Sep 18 08:06:40 EDT 2006


> Message: 6
> Date: Fri, 15 Sep 2006 18:36:35 +0300
> From: "Anatoly Zaretsky" <anatoly.zaretsky at gmail.com>
> Subject: Re: [Haskell-cafe] Why is type 'b' forced to be type 'm a'
> 	and not	possibly 'm a -> m a'
> To: "Vivian McPhail" <vivian.mcphail at paradise.net.nz>
> Cc: Haskell Cafe <haskell-cafe at haskell.org>
> Message-ID:
> 	<a21cb60a0609150836u5695cf41jfbb31530105bec3a at mail.gmail.com>
> Content-Type: text/plain; charset=ISO-8859-1; format=flowed
> 
> On 9/15/06, Vivian McPhail <vivian.mcphail at paradise.net.nz> wrote:
> >
> > class Forkable a where
> >     fork :: String -> a -> a -> a
> >
> > ...
> > {-
> > instance (Monad m, Forkable (m a), Forkable b) => Forkable (m a -> b)
where
> >     fork n a1 a2 a = do
> >                      a' <- a
> >                      fork n (a1 $ return a') (a2 $ return a')
> > -}
> >
> 
> Let's do manual type checking.
> First, fork :: Forkable a => String -> a -> a -> a
> So for Forkable (m a -> b)
>   fork :: String -> (m a -> b) -> (m a -> b) -> m a -> b
> Then
>   fork n a1 a2 a :: b
> But you define it as
>   fork n a1 a2 a = do {...}
> So it should be of type Monad t => t a, not just any `b'.
> 
> Instead, you can define
>   instance (Monad m, Forkable (m b)) => Forkable (m a -> m b) where
>     ...
> 

Well, I can partially instantiate what I am trying to achieve by enumerating
cases.  Note that when the first type is a monadic type the computation gets
evaluated and then forked, but when the first type is a function it merely
gets passed.  My problem is that there are a very large number of possible
cases.  So in the case Forkable (m a -> b), a number of instances of which I
can implement (e.g. Forkable (m a -> m a -> m a), Forkable ((m a -> m a) ->
m a), and Forkable (m a -> (m a -> m a) -> m a)), I don't see why 'b' should
necessarily typecheck to 't t1'.

What I would like to be able to do is differentiate between Forkable (m a ->
b) and Forkable (<function type> -> b).

By the way, the following code typechecks and runs correctly, my problem is
that enumerating all possible types requires five factorial (120) different
instances, and to a lazy functional programmer who can 'see' the pattern it
seems that there must be a nicer way of achieving my end.

\begin{code}
instance (Monad m, Forkable (m a)) => Forkable (m a -> m a) where
    fork n a1 a2 a = do
                     a' <- a
                     fork n (a1 $ return a') (a2 $ return a')

instance (Monad m, Forkable (m a)) => Forkable (m a -> m a -> m a) where
    fork n a1 a2 a b = do
                       a' <- a
                       fork n (a1 $ return a') (a2 $ return a') b

instance (Monad m, Forkable (m a)) => Forkable ((m a -> m a) -> m a) where
    fork n a1 a2 a = do
                     fork n (a1 a) (a2 a)

instance (Monad m, Forkable (m a)) => Forkable (m a -> (m a -> m a) -> m a)
where
    fork n a1 a2 a b = do
                       a' <- a
                       fork n (a1 $ return a') (a2 $ return a') b

\end{code}

> Note that to compile it you also need -fallow-undecidable-instances
> and -fallow-overlapping-instances.
> 
> --
> Tolik
> 

Thanks for your help so far!
>
>

Cheers,

Vivian

-- 
No virus found in this outgoing message.
Checked by AVG Free Edition.
Version: 7.1.405 / Virus Database: 268.12.4/449 - Release Date: 15/09/2006
 



More information about the Haskell-Cafe mailing list