[Haskell-cafe] Different behaviour with -XAllowAmbiguousTypes in 7.10.3b and 8.0.1
Adam Gundry
adam at well-typed.com
Tue Jul 26 08:24:38 UTC 2016
Hi Max,
I think 7.10.3 is correct to reject both programs. The `get` function
with a type signature is ambiguous, even when AllowAmbiguousTypes is
enabled, because there is no reason for GHC to pick `e` and `a` when
instantiating the type variables in the call to `fsmRead`.
In general, if a function's type can be inferred, it should be possible
to give it a signature with that type. 8.0.1 apparently doesn't respect
this property, which is a bug.
AllowAmbiguousTypes should make it possible to write a function with the
same type signature as `get`, e.g. by using TypeApplications to fix the
variables:
get :: forall st s e a. (FSMStore st s e a) => st -> String -> s
get st i = fsmRead @st @s @e @a st i
Of course, this merely defers the ambiguity to the call sites of `get`.
Hope this helps,
Adam
On 20/07/16 16:52, Max Amanshauser wrote:
> Hi,
>
> while porting a library to Haskell, which deals with persisting finite state automata to various stores, depending on the user's choice and the instances provided for types s(tate) e(vent) a(ction), I ran into different behaviour in ghc 7.10.3b and 8.0.1 related to ambiguity checks. This is a minimised and somewhat contrived example:
>
>> -- testme.hs
>>
>> {-# LANGUAGE MultiParamTypeClasses #-}
>> {-# LANGUAGE FlexibleInstances #-}
>> {-# LANGUAGE AllowAmbiguousTypes #-}
>>
>> module TestMe where
>>
>> data MyStore = MyStore
>>
>> class FSMStore st s e a where
>> fsmRead :: st -> String -> s
>>
>> instance (Num s) => FSMStore MyStore s e a where
>> fsmRead st i = 23
>>
>> get :: (FSMStore st s e a) => st -> String -> s
>> get st i = fsmRead st i
>
> With GHC 8.0.1 I get:
>
>> *TestMe> :l test.hs
>> [1 of 1] Compiling TestMe ( test.hs, interpreted )
>>
>> test.hs:19:12: error:
>> • Could not deduce (FSMStore st s e0 a0)
>> arising from a use of ‘fsmRead’
>> from the context: FSMStore st s e a
>> bound by the type signature for:
>> get :: FSMStore st s e a => st -> String -> s
>> at test.hs:18:1-47
>> The type variables ‘e0’, ‘a0’ are ambiguous
>> Relevant bindings include
>> st :: st (bound at test.hs:19:5)
>> get :: st -> String -> s (bound at test.hs:19:1)
>> These potential instance exist:
>> instance Num s => FSMStore MyStore s e a
>> -- Defined at test.hs:12:10
>> • In the expression: fsmRead st i
>> In an equation for ‘get’: get st i = fsmRead st i
>> Failed, modules loaded: none.
>
> However, when I remove the type signature for get:
>
>> Prelude> :l test.hs
>> [1 of 1] Compiling TestMe ( test.hs, interpreted )
>> Ok, modules loaded: TestMe.
>> *TestMe> :t get
>> get :: FSMStore st s e a => st -> String -> s
>> *TestMe> get MyStore "asdf"
>> 23
>
> GHC inferred the exact same type I provided, but this time it compiles successfully.
>
> When going back to GHC 7.10.3b, without type signature:
>
>> GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help
>> :Prelude> :l test.hs
>> [1 of 1] Compiling TestMe ( test.hs, interpreted )
>>
>> test.hs:19:1:
>> Could not deduce (FSMStore st s e0 a0)
>> from the context (FSMStore st s e a)
>> bound by the inferred type for ‘get’:
>> FSMStore st s e a => st -> String -> s
>> at test.hs:19:1-23
>> The type variables ‘e0’, ‘a0’ are ambiguous
>> When checking that ‘get’ has the inferred type
>> get :: forall st s e a. FSMStore st s e a => st -> String -> s
>> Probable cause: the inferred type is ambiguous
>> Failed, modules loaded: none.
>
> So my questions are:
> *) What's with the different behaviour depending on whether the type sig is inferred or provided?
> *) Is GHC 7.10.3b or 8.0.1 closer to the correct behaviour w.r.t. -XAllowAmbiguousTypes?
>
> --
> Regards,
> Max Amanshauser.
More information about the Haskell-Cafe
mailing list