I know this is code is a bit silly, but can someone explain why this isList [42] returns True whereas isList2 [42] prints False, and how to prevent this? I'd like to get better understanding of some of the more obscure GHC type extensions, and I thought this would be an interesting example to figure out.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE IncoherentInstances #-}
class IsList a where
isList :: a -> Bool
instance IsList a where
isList x = False
instance IsList [a] where
isList x = True
isList2 = isList
main =
print (isList 42) >>
print (isList2 42) >>
print (isList [42]) >>
print (isList2 [42])
It's really quite simple. Let's ask GHCi what the type of isList2 is:
∀x. x ⊢ :t isList2
isList2 :: a -> Bool
This doesn't match the [a] instance (even though it could, via unification), but it does match the a instance immediately. Therefore, GHC selects the a instance, so isList2 returns False.
This behavior is precisely what IncoherentInstances means. Actually, this is a rather nice demonstration of it.
Hilariously, if you simply disable IncoherentInstances, we get exactly the opposite effect, and GHCi now says this:
∀x. x ⊢ :t isList2
isList2 :: [Integer] -> Bool
This happens because isList2 is a top-level binding not defined using function syntax, and thus subject to the Dreaded Monomorphism Restriction. So it gets specialized to the instance it's actually used with.
Adding NoMonomorphismRestriction as well as disabling IncoherentInstances, we get this instead:
∀x. x ⊢ :t isList2
isList2 :: IsList a => a -> Bool
∀x. x ⊢ isList2 'a'
False
∀x. x ⊢ isList2 "a"
True
∀x. x ⊢ isList2 undefined
<interactive>:19:1:
Overlapping instances for IsList a0 arising from a use of `isList2'
Which is the expected overlapping behavior, with the instance chosen based on use and complaints if the choice is ambiguous.
Regarding the edit to the question, I don't believe the desired result is possible without type annotations.
The first option is to give isList2 a type signature, which prevents IncoherentInstances from selecting an instance too early.
isList2 :: (IsList a) => a -> Bool
isList2 = isList
You'll probably need to do the same anywhere else isList is mentioned (even indirectly) without being applied to an argument.
The second option is to disambiguate the numeric literals and disable IncoherentInstances.
main =
print (isList (42 :: Integer)) >>
print (isList2 (42 :: Integer)) >>
print (isList [42]) >>
print (isList2 [42])
In this case, there's enough information to pick a most-specific instance, so OverlappingInstances does its thing.
The following code does the trick without requiring IncoherentInstances:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverlappingInstances #-}
class IsList a where
isList :: a -> Bool
instance IsList a where
isList x = False
instance IsList [a] where
isList x = True
isList2 :: (IsList a) => a -> Bool
isList2 = isList
main = do
print (isList (42 :: Int))
print (isList [42 :: Int])
print (isList2 (42 :: Int))
print (isList2 [42 :: Int])
I'd recommend not using IncoherentInstances, it seems to cause a lot of trouble, as you can silently call different overloads depending on context quite easily.
Related
We can get a value level proof that [Int] has a Show instance using a Dict
{-# LANGUAGE ConstraintKinds, GADTs #-}
data Dict (p :: Constraint) where
Dict :: p => Dict p
and
proof = Dict :: Dict (Show [Int])
Is there a way to get a value level derivation, that is, the entire proof tree ?
derivation = Apply#Int(Lam a.(Show a) :=> Show [a])) (Apply(() :=> Show Int)())
There isn't a way to get the derivation of an arbitrary constraint as a Haskell value.
The closest thing I can think of, if you want to check whether the derivation is what you think it is, is to look at the desugarer output.
ghc -ddump-ds -ddump-to-file A.hs
The relevant part looks like this:
-- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0}
irred :: Show [Int]
[LclId]
irred = GHC.Show.$fShow[] # Int GHC.Show.$fShowInt
-- RHS size: {terms: 2, types: 3, coercions: 0, joins: 0/0}
proof :: Dict (Show [Int])
[LclIdX]
proof = Cns.Dict # (Show [Int]) irred
Another one is to write custom typeclasses instrumented to reflect the derivation, either in types or in values, but of course this doesn't apply to preexisting type classes.
{-# LANGUAGE AllowAmbiguousTypes, ConstraintKinds, GADTs, DataKinds,
FlexibleInstances, KindSignatures, MultiParamTypeClasses, RankNTypes,
ScopedTypeVariables, TypeApplications, TypeOperators,
UndecidableInstances #-}
import Data.Typeable
import Data.Kind
data (c :: [Type]) :=> (d :: Type -> Constraint)
class MyShow a d where
myshow :: a -> String
instance (d ~ ('[] :=> MyShow Int)) => MyShow Int d where
instance (MyShow a da, d ~ ('[da] :=> MyShow [a])) => MyShow [a] d where
myshowInstance :: forall a d. (Typeable d, MyShow a d) => TypeRep
myshowInstance = typeRep #_ #d Proxy
main = print (myshowInstance #[Int])
The output could be made to look better, e.g., via a singleton with a proper rendering method instead of TypeRep, but I hope you get the main idea.
:=> (': * (:=> ('[] *) (MyShow Int)) ('[] *)) (MyShow [Int])
This may be what you're after, or at least enough to give you a general idea. I can't think of a way to have GHC provide this automatically, but you can manually construct the chain of entailments that proves the constraint using the constraints package.
For whatever reason, there is no instance () :=> Show Int, so I've used Char instead. This is likely an oversight, I've opened a pull request to add the missing instances.
{-# LANGUAGE ConstraintKinds #-}
import Data.Constraints
derivation :: () :- Show [Char]
derivation = trans showList showChar
where showList :: Show a :- Show [a]
showList = ins
showChar :: () :- Show Char
showChar = ins
Unfortunately printing this value doesn't show the inner derivations, just "Sub Dict".
A fun exercise could be to try to write derivation with explicit TypeApplications using Data.Constraint.Forall. You'll need a couple extra steps to prove Show a :- Forall Show and ForallF Show [] :- Show [a].
This (somewhat nonsensical) module compiles:
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ExplicitForAll #-}
module Foo where
class A t where
f :: forall x m. Monoid x => t m -> m
f = undefined
instance A [] where
f = undefined
If I remove the instance's definition of f, I would expect it to inherit the method default and amount to the same thing.
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ExplicitForAll #-}
module Foo where
class A t where
f :: forall x m. Monoid x => t m -> m
f = undefined
instance A [] where
This does not work, however. GHC 8.0.2 gives this error:
• Could not deduce (Monoid x0)
arising from a use of ‘Foo.$dmf’
from the context: Monoid x
bound by the type signature for:
f :: Monoid x => [m] -> m
at src/Foo.hs:10:10-13
The type variable ‘x0’ is ambiguous
These potential instances exist:
instance Monoid a => Monoid (IO a) -- Defined in ‘GHC.Base’
instance Monoid Ordering -- Defined in ‘GHC.Base’
instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
...plus 7 others
(use -fprint-potential-instances to see them all)
• In the expression: Foo.$dmf #[]
In an equation for ‘f’: f = Foo.$dmf #[]
In the instance declaration for ‘A []’
I'm not sure how to read this error, because I don't know where the imaginary x0 is being inserted. Why doesn't the second example compile?
GHC is basically converting your code to this:
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ExplicitForAll #-}
module Foo where
defaultF :: forall t x m. (A t, Monoid x) => t m -> m
defaultF = undefined
class A t where
f :: forall x m. Monoid x => t m -> m
f = defaultF #t #x #m
instance A [] where
f = defaultF #[]
Now, in the last line the type variable x is not in scope since we do not have an explicit forall x. Even if it were, it is not passed to defaultF as an explicit type argument. So, the last defaultF call could be made on any monoid at all, possibly another one!
For that call, the inference engine generates a fresh x0 type variable, hence the type error message :-(
Maybe GHC's instance deriving mechanism should be updated, now that ambiguous types are allowed (which is a good thing, IMO).
For a simpler case, consider
a :: forall x. Monoid x => Int
a = undefined
b :: forall x. Monoid x => Int
b = a
The last call needs a disambiguating explicit type argument, in Haskell. It would work fine in dependently typed languages like Agda/Idris/Coq/... since these (by default, at least) pass their type arguments explicitly.
I have promoted type Nat = Suc Nat | Zero and I want to make a typeclass class C (a :: Nat) b. Is there a way to convince GHC that instance C Zero b and instance C (Seq x) b covers all cases and therefore I don't need to explicitly declare C as a constraint whenever I use the class' methods. Here is some code:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE IncoherentInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
-- Some of these may not be necessary for the particular snippet.
data Nat = Zero | Suc Nat
-- TypeApplications, I know. I am traditional.
data NProxy :: Nat -> * where
NProxy :: NProxy n
class C (a :: Nat) b where
f :: NProxy a -> b -> Maybe b
instance C Zero b where
f _ _ = Nothing
instance C (Suc a) b where
f _ = Just
-- instance C n b where
-- f = error "This should not have been reached using GetNum."
class C1 a where
f1 :: a -> Maybe a
instance C1 a where
f1 = Just
type family GetNum a :: Nat where
GetNum Char = (Suc Zero)
GetNum Int = Suc (Suc Zero)
GetNum [x] = Suc (GetNum x)
GetNum a = Suc Zero
-- Error:
-- • No instance for (C (GetNum a) a) arising from a use of ‘f’
-- • In the expression: f (NProxy :: NProxy (GetNum a)) x
-- In an equation for ‘noGreet’:
-- noGreet x = f (NProxy :: NProxy (GetNum a)) x
noGreet :: forall a . a -> Maybe a
noGreet x = f (NProxy :: NProxy (GetNum a)) x
-- This one works fine though.
dumb :: a -> Maybe a
dumb = f1
Edit: A related question would be, given the commented out instance if C, why is it when I say noGreet "hi" to the repl I get an exception and not Just "hi".
noGreet :: forall a . a -> Maybe a
Parametricity says the only definable values of this type are things like
noGreet x = Just x
noGreet x = Nothing
noGreet x = undefined
noGreet x = x `seq` Just x
...
We can't make any choices that depend on the type a, like "Nothing if a is Char otherwise Just x".
"Tricking the type checker" is a red herring, since what is preventing you from writing such a function is not the type checker, but the fact that information about the type a is simply not available at all at runtime.
When you used IncoherentInstances in
noGreet :: forall a . a -> Maybe a
noGreet x = f (NProxy :: NProxy (GetNum a)) x
the compiler had to choose which C instance to use for the call to f, since there is no context provided in the type of noGreet. Naturally the only one that applied was
instance C n b where f = error "This should not have been reached using GetNum."
as the other two instances are too specific to use when we know nothing about a.
Using ViewPatterns and Data.Typeable, I’ve managed to write a function that allows me to write something resembling case analysis on types. Observe:
{-# LANGUAGE GADTs, PatternSynonyms, RankNTypes, ScopedTypeVariables
, TypeApplications, TypeOperators, ViewPatterns #-}
import Data.Typeable
viewEqT :: forall b a. (Typeable a, Typeable b) => a -> Maybe ((a :~: b), b)
viewEqT x = case eqT #a #b of
Just Refl -> Just (Refl, x)
Nothing -> Nothing
evilId :: Typeable a => a -> a
evilId (viewEqT #Int -> Just (Refl, n)) = n + 1
evilId (viewEqT #String -> Just (Refl, str)) = reverse str
evilId x = x
The above evilId function is very evil, indeed, since it uses Typeable to completely subvert parametricity:
ghci> evilId True
True
ghci> evilId "hello"
"olleh"
Since I love being evil, I am very pleased with this, but the above syntax is very noisy. I would love to be able to write the same code more clearly, so I decided to write a pattern synonym:
pattern EqT :: forall b a. (Typeable a, Typeable b) => (a ~ b) => b -> a
pattern EqT x <- (viewEqT #b -> Just (Refl, x))
I figured that I would be able to use this pattern synonym to make my evil case analysis much easier to read:
evilId :: Typeable a => a -> a
evilId (EqT (n :: Int)) = n + 1
evilId (EqT (str :: String)) = reverse str
evilId x = x
Sadly, this does not work at all. GHC does not seem to consult my type annotations before typechecking the pattern, so it believes b is an ambiguous variable in each pattern. Is there any way I can cleanly wrap these patterns with a pattern synonym, or will I be stuck with my longer view patterns?
If the goal is to find some clean syntax to implement your evilId function, you can write it like this:
{-# Language ScopedTypeVariables, GADTs, TypeApplications #-}
module Demo where
import Data.Typeable
evilId :: forall a. Typeable a => a -> a
evilId x
| Just Refl <- eqT #a #Int = x+1
| Just Refl <- eqT #a #String = reverse x
| otherwise = x
This doesn't help with the ambiguities surrounding your pattern synonyms, unfortunately.
I am using makeFields from lens to generate fields overloaded for various structures. I would like to use these fields at one with multiple structures while having to state which field I want to use only once. It would look like this:
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
import Control.Lens
data A = A
{ _aX :: String
, _aY :: String
}
makeFields ''A
data B = B
{ _bX :: String -> Char
, _bY :: String -> Bool
}
makeFields ''B
-- x can get _aX from an A and _bX from a B
a :: A
a = undefined
b :: B
b = undefined
q :: (Getter A String) AND (Getter B (String -> a)) -> a
q lens = (b^.lens) (a^.lens)
Which type should I give q? I tried letting GHC infer the types, but that failed.
To decide what is to be done, we need to know what the types of your (makeField-generated) fields are:
GHCi> :t x
x :: (HasX s a, Functor f) => (a -> f a) -> s -> f s
So the abstraction covering all your x-bearing types (the abstraction I was whining about before noticing you were using makeFields) is a multi-parameter type class HasX, and similarly for the other fields. That gives us enough to use x with different types in a single implementation:
-- Additional extension required: FlexibleContexts
-- Note that GHC is able to infer this type.
qx :: (HasX t (a -> b), HasX s a) => t -> s -> b
qx t s = (t ^. x) (s ^. x)
GHCi> import Data.Maybe
GHCi> let testA = A "foo" "bar"
GHCi> let testB = B (fromMaybe 'ø' . listToMaybe) null
GHCi> qx testB testA
'f'
That, however, is not quite what you asked for. You wanted something like:
q xOrY b a = (b^.xOrY) (a^.xOrY)
Achieving that, however, requires abstracting over the classes HasX, HasY, etc. Doing so is, in fact, somewhat feasible thanks to the ConstraintKinds extension, as demonstrated in Could we abstract over type classes? Here it goes:
-- Additional extensions required: ConstraintKinds, ScopedTypeVariables
-- Additional import required: Data.Proxy
-- GHC cannot infer this type.
q :: forall h s t a b. (h t (a -> b), h s a) => Proxy a -> Proxy h
-> (forall u c. h u c => Getting c u c) -> t -> s -> b
q _ _ l t s =
(t ^. (l :: Getting (a -> b) t (a -> b))) (s ^. (l :: Getting a s a))
GHCi> q (Proxy :: Proxy String) (Proxy :: Proxy HasX) x testB testA
'f'
The first proxy, which determines the intermediate type, is necessary unless you give up this bit of generality and replace a by String. Additionally, you have to specify the field twice, both by passing the getter as an argument and through the second proxy. I am not at all convinced that this second solution is worth the trouble -- the extra boilerplate of having to define qx, qy, etc. looks quite a bit less painful than all the circuitousness involved here. Still, if any of you who are reading this would like to suggest an improvement, I'm all ears.