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

2006-09-20 Thread tpledger
Vivian McPhail wrote:
> > > class Forkable a where
> > > fork :: String -> a -> a -> a

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

Have you tried this combination of instances?

instance Forkable (IO a) where ...
-- and similarly for all the concrete
-- monad types you will use fork with

instance (Forkable a, Forkable b) =>
 Forkable (a -> b) where ...

Alternatively, since the fork function seems to be all about
propagating a value (the String), would Control.Monad.Reader
serve your purpose?

Regards,
Tom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-09-20 Thread Vivian McPhail
> Vivian McPhail wrote:
> > > > class Forkable a where
> > > > fork :: String -> a -> a -> a
> 
> > What I would like to be able to do is
> > differentiate between Forkable (m a ->
> > b) and Forkable ( -> b).
> 
> Have you tried this combination of instances?
> 
> instance Forkable (IO a) where ...
> -- and similarly for all the concrete
> -- monad types you will use fork with
> 
> instance (Forkable a, Forkable b) =>
>  Forkable (a -> b) where ...
> 
> Alternatively, since the fork function seems to be all about
> propagating a value (the String), would Control.Monad.Reader
> serve your purpose?

The value that gets 'forked' is not actually the string, it is the result of
a monadic computation.

> 
> Regards,
> Tom
> 

I have tried:

> instance Forkable (USM NRef) where...

Which is my Monad

The problem lies with 

> instance (Forkable a, Forkable b) => Forkable (a -> b) where
> fork n a1 a2 a = fork n (a1 a) (a2 a)

because I need the arg a to be evaluated before it gets passed to a1 and a2.
This definition does the right thing when type 'a' is a function type,
because it is not a value, but with something like 'm a -> (m a -> m a) -> m
a' with Forkable (a -> b) the first arg gets evaluated twice, to be more
concrete:

With

(and golden white) eggs

I want the 'eggs' that is passed to 'golden' to be the same as the 'eggs'
that is passed to 'white', i.e.

-> and1 (golden2 eggs3) (white4 eggs3) and not -> and1 (golden2 eggs3)
(white4 eggs5)

So to do this I need to be able to recognise the case where the 'a' of (a ->
b) is of type 'm a' so that I can evaluate it

-- doesn't typecheck
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')

Tom suggested that I might be able to use the Reader monad, but I'm not
clear as to how I could do this.

Cheers,

Vivian





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

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


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

2006-10-01 Thread tpledger
Vivian McPhail wrote:
...
> I need the arg a to be evaluated before it gets
> passed to a1 and a2. This definition does the right thing
> when type 'a' is a function type, because it is not a
> value, but with something like 'm a -> (m a -> m a) -> m
> a' with Forkable (a -> b) the first arg gets evaluated
> twice, to be more concrete:
>
> With
>
> (and golden white) eggs
>
> I want the 'eggs' that is passed to 'golden' to be the
> same as the 'eggs' that is passed to 'white', i.e.
...

Could you reduce the need for Forkable instances, by
rewriting '(and golden white) eggs' as 'and golden white =<<
eggs'?  Or would the same piece of code also have to handle
combinations such as monadic 'and golden white' and
non-monadic eggs?

[BTW, thanks for giving me a pretext to use the phrase
non-monadic eggs!]

> Tom suggested that I might be able to use the Reader monad
> , but I'm not clear as to how I could do this.

Please ignore that.  I only mentioned it in case the sole
purpose of fork was to propagate a String, which you've now
explained is not so.

Regards,
Tom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2006-09-18 Thread Vivian McPhail
> Message: 6
> Date: Fri, 15 Sep 2006 18:36:35 +0300
> From: "Anatoly Zaretsky" <[EMAIL PROTECTED]>
> Subject: Re: [Haskell-cafe] Why is type 'b' forced to be type 'm a'
>   and not possibly 'm a -> m a'
> To: "Vivian McPhail" <[EMAIL PROTECTED]>
> Cc: Haskell Cafe 
> Message-ID:
>   <[EMAIL PROTECTED]>
> Content-Type: text/plain; charset=ISO-8859-1; format=flowed
> 
> On 9/15/06, Vivian McPhail <[EMAIL PROTECTED]> 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 ( -> 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
 

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