As an interesting side-note, this code compiles and does not issue a warning:
instance (Show a, Impl_ D1 D2 ~ (a -> IO ())) => Dispatch D1 D2 where
   type Impl_ D1 D2 = Impl_ D1 D2
   runF _ _ = print

And even seems to resolve correctly:
*Main> runF (undefined :: D1) (undefined :: D2)

<interactive>:11:1:
    No instance for (Show (a0 -> IO ())) arising from a use of ‘print’
    In a stmt of an interactive GHCi command: print it

But when I run it the REPL goes into an infinite loop:
*Main> runF (undefined :: D1) (undefined :: D2) 1
*** Exception: <<loop>>

-deech

On Sun, Jan 4, 2015 at 8:33 AM, aditya siram <aditya.siram@gmail.com> wrote:
Hi,
Unfortunately while this compiles it does not work correctly. For example the code:
data D1
data D2
class Dispatch a b where
   type Impl_ a b :: *
   runF :: a -> b -> Impl_ a b
instance (Show a, Impl_ D1 D2 ~ (a -> IO ())) => Dispatch D1 D2 where
   runF _ _ = print

compiles with the warning:
    No explicit associated type or default declaration for ‘Impl_’
    In the instance declaration for ‘Dispatch D1 D2’

But however when I run it I see that the type function does not resolve:
*Main> runF (undefined :: D1) (undefined :: D2)

<interactive>:8:1:
    Couldn't match expected type ‘a0 -> IO ()’
                with actual type ‘Impl_ D1 D2’
    The type variable ‘a0’ is ambiguous
    In the first argument of ‘print’, namely ‘it’
    In a stmt of an interactive GHCi command: print it

Thanks!
-deech




On Sat, Jan 3, 2015 at 8:59 AM, aditya siram <aditya.siram@gmail.com> wrote:
Hi,
That seemed to compile! I had no idea this kind of construction was even possible!

However it did spew out a bunch of warnings like:
"No explicit associated type or default declaration for ‘Impl’ in instance ..."

Thanks!
-deech

On Fri, Jan 2, 2015 at 1:38 PM, Erik Hesselink <hesselink@gmail.com> wrote:
Could you do something like this?

    instance (Impl D1 D2 ~ a -> IO (), C a) => Dispatch D1 D2

Erik

On Fri, Jan 2, 2015 at 7:59 PM, aditya siram <aditya.siram@gmail.com> wrote:
> Hi all,
> I'd like to be able to constrain an associated type.
>
> I used to have an instance that looked like:
> class Dispatch a b c | a b -> c where
>    runF :: a -> b -> c
> instance (C a) => Dispatch D1 D2 ( a -> IO ()) where
>    runF d1 d2 = (\_ -> return ())
>
> Since I upgraded to 7.8 from 7.5 that instance declaration is no longer
> accepted is no longer accepted since it violates FD's.
>
> I have been updating my code to use type families like so:
> class Dispatch a b where
>    type Impl a b :: *
>    runF :: a -> b -> Impl a b
> instance (C a) => Dispatch D1 D2 where
>    type Impl D1 D2 = a -> IO ()
>    runF d1 d2 = (\_ return ())
>
> Unfortunately the `type Impl ...` line in the instance is rejected because
> it uses `a` on the RHS.
>
> In this one case I could just package it up into a newtype or something but
> I would ideally like to be able to constrain any number of arguments like:
> instance (C a, C b ... C z) => Dispatch D1 D2 where
>    type Impl D1 D2 = a -> b -> ... -> z -> IO ()
>    ...
>
> This was something I could do in 7.6 (although I realize this is way safer).
> How do I go about getting that constraint back?
>
> Thanks!
> -deech
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>