Hi,

It looks like an effect of ExtendedDefaultRules: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html#extension-ExtendedDefaultRules

It's hard to tell without the code but maybe something like that will do:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

add :: forall a b1 b2 b3. (Num a, Newtype a b1, Newtype a b2, Newtype a b3) => b2 -> b3 -> b1
add x y = wrap @a @b1 $ unwrap @a x + unwrap @a y

-Sylvain

On 10/04/2019 12:32, Michel Haber wrote:
Hello Cafe,

I was trying to load a module containing this function in ghci:
"add x y = wrap $ unwrap x + unwrap y"
with the following extensions activated:

ConstraintKinds
DataKinds
DeriveFunctor
DuplicateRecordFields
FlexibleContexts
FlexibleInstances
GADTs
KindSignatures
MultiParamTypeClasses
PolyKinds
TypeFamilies
TypeOperators
AllowAmbiguousTypes

And it loaded without problem.

So then I tested its type with ":t add", which gave:
add :: (Num a, Newtype a b1, Newtype a b2, Newtype a b3) => b2 -> b3 -> b1

Then I added this signature to the function in the module. This caused ghci
to refuse to load it and give the following error:

src/Exercises.hs:55:11: error:
    • Could not deduce (Newtype Integer b1)
        arising from a use of ‘wrap’
      from the context: (Num a, Newtype a b1, Newtype a b2, Newtype a b3)
        bound by the type signature for:
                   add :: forall a b1 b2 b3.
                          (Num a, Newtype a b1, Newtype a b2, Newtype a b3) =>
                          b2 -> b3 -> b1
        at src/Exercises.hs:54:1-74
    • In the expression: wrap $ unwrap x + unwrap y
      In an equation for ‘add’: add x y = wrap $ unwrap x + unwrap y
   |
55 | add x y = wrap $ unwrap x + unwrap y
   |           ^^^^^^^^^^^^^^^^^^^^^^^^^^

src/Exercises.hs:55:18: error:
    • Could not deduce (Newtype Integer b2)
        arising from a use of ‘unwrap’
      from the context: (Num a, Newtype a b1, Newtype a b2, Newtype a b3)
        bound by the type signature for:
                   add :: forall a b1 b2 b3.
                          (Num a, Newtype a b1, Newtype a b2, Newtype a b3) =>
                          b2 -> b3 -> b1
        at src/Exercises.hs:54:1-74
    • In the first argument of ‘(+)’, namely ‘unwrap x’
      In the second argument of ‘($)’, namely ‘unwrap x + unwrap y’
      In the expression: wrap $ unwrap x + unwrap y
   |
55 | add x y = wrap $ unwrap x + unwrap y
   |                  ^^^^^^^^

src/Exercises.hs:55:29: error:
    • Could not deduce (Newtype Integer b3)
        arising from a use of ‘unwrap’
      from the context: (Num a, Newtype a b1, Newtype a b2, Newtype a b3)
        bound by the type signature for:
                   add :: forall a b1 b2 b3.
                          (Num a, Newtype a b1, Newtype a b2, Newtype a b3) =>
                          b2 -> b3 -> b1
        at src/Exercises.hs:54:1-74
    • In the second argument of ‘(+)’, namely ‘unwrap y’
      In the second argument of ‘($)’, namely ‘unwrap x + unwrap y’
      In the expression: wrap $ unwrap x + unwrap y
   |
55 | add x y = wrap $ unwrap x + unwrap y
   |                             ^^^^^^^^
Failed, no modules loaded.

This does not make sense to me, since I only used the signature that ghci itself gave me.

Is this a bug? if not, could someone please explain this behaviour to me?

Thanks,
Michel

_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.