Constraint on method depends on instances in scope? - haskell

Consider this code:
{-# language FlexibleInstances, UndecidableInstances #-}
module Y where
class C m where
x :: m
instance {-# overlappable #-} Monoid m => C m where
x = mempty
instance C Int where
x = 53
What is the type of x?
λ :type x
x :: C m => m
So far — so good. Now remove the Int instance. What is the type of x?
λ :type x
x :: Monoid m => m
Surprise!
Why is this happening?

This behaviour is explained in the following blog post:
Opaque constraint synonyms
In short: GHC is smart enough to see that you have only one instance of the C typeclass and decided that it's the only possible instance, so every time it sees C m constraint, it replaces it with Monoid m because they are equivalent.
N.B. As #chi further explains in a comment:
When GHC finds a constraint C t, it tries to solve it. If if finds a matching instance (...) => C t where ..., the constraint is replaced with the context (...). This is repeated as much as possible. The final constraint appears in the type (or triggers a "unsolved" type error). This process is justified since there can only be at most one matching instance. Overlapping instances change this, and prevent this context reduction when multiple instances (in scope!) match, roughly. It is a fragile extension, to be used with some care.

Related

How do the various "..Instances" pragma's work together, and is there a way around my current problem?

Consider the following code:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
class X a
class Y a
instance Y Bool
instance (Y a) => X a
instance {-# OVERLAPPING #-} X Int
f :: (X a) => a -> a
f x = x
These LANGUAGE pragma's are needed to write the above instances.
Now, say we want to write a function g:
g :: (Y a) => a -> a
g = f
Without IncoherentInstances or adding {-# INCOHERENT #-} to one of the instances, this doesn't typecheck.
But when we do add this, and ask ghci
ghci> :t f
f :: Y a => a -> a
Suddenly the type of 'f' changed?
With this small example, programs still typecheck when I give f an Int (indicating that the above would be merely a 'visual bug', but in a bigger example the same does not typecheck, giving me an error like:
Could not deduce (Y a) arising from a use of 'f
(...)
from the context: (..., X a, ...)
This also happens when we say
h = f
and try to call h with an Int
:type f does not report the type of the defined entity f. It reports the type of the expression f. GHC tries really hard to stamp polymorphism out of expressions. In particular, using f in an expression triggers simplification of the X a constraint (as does using any definition with a constraint). Without IncoherentInstances, GHC refrains from using instance Y a => X a, because there is another instance that overlaps it, so GHC needs to wait to see which one it should use. This ensures coherence; the only X Int instance that is ever used is the explicitly "specialized" one. With IncoherentInstances, you say that you don't care about coherence, so GHC goes ahead and simplifies X a to Y a using the polymorphic instance whenever f appears in an expression. The weird behavior you see where sometimes GHC is OK with using X Int and sometimes complains that there is no Y Int is a result of GHC making different internal decisions about when it wants to simplify constraints (you did ask for incoherence!). The command for seeing the type of a definition is :type +v. :type +v f should show the type of f "as declared". Hopefully, you can also see that IncoherentInstances is a bad idea. Don't use it.

GHC stuck due to UndecidableSuperClasses - expected behaviour or bug?

The following snippet makes GHC (checked with 8.6.2 & 8.4.4) stuck during compilation:
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
import GHC.Exts (Constraint)
data T = T
type family F t (c :: * -> Constraint) :: Constraint
type instance F T c = c T
class F t C => C t where
t :: C T => t
t = undefined
I think that it gets stuck because for t GHC tries to find C T, which leads to F T C which expands via type family F back to C T, which is what it was looking for (infinite loop).
I suppose that theoretically GHC could tell that it reached its quest for C T from itself and that anything that depends on itself can work fine recursively, or am I misunderstanding something?
Side note: in the real example where I stumbled upon this behaviour I was able to achieve what I wanted without the compiler being stuck by replacing UndecidableSuperClasses with Data.Constraint.Dict instead.
UndecidableSuperClasses does not make instance resolution lazy. The compiler will still expand superclass constraints as far as possible. I believe that the fields in instance dictionaries that point to the superclass dictionaries are strict, and GHC actually pins them down at compile time. This is in contrast to UndecidableInstances, which allows instance constraints to be treated (a bit) lazily.
deriving instance Show (f (Fix f)) => Show (Fix f)
will work just fine. When resolving an instance for, e.g., Show (Fix Maybe)), GHC will see that it needs Show (Maybe (Fix Maybe)). It then sees it needs Show (Fix Maybe) (which it's currently resolving) and accept that thanks to UndecidableInstances.
All UndecidableSuperClases does is disable the checks that guarantee that expansion won't loop. See the bit near the beginning of Ed Kmett's talk where he describes the process "reaching a fixed point".
Consider a working example (ripped from Data.Constraint.Forall):
type family Skolem (p :: k -> Constraint) :: k
class p (Skolem p) => Forall (p :: k -> Constraint)
GHC only accepts this with UndecidableSuperclasses. Why? Because it doesn't know anything about what that constraint might mean. As far as it knows, it could be the case that p (Skolem p) will reduce to Forall p. And that could actually happen!
class Forall P => P x
-- This definition loops the type checker
foo :: P x => x
foo = undefined

Overlapping instances - how to circumvent them

I am a beginner at Haskell, so please be indulgent. For reasons that are not important here, I am trying to define a operator <^> that takes a function and an argument and returns the value of the function by the argument, irrespective of which of the function and the argument came first. In short, I would like to be able to write the following:
foo :: Int -> Int
foo x = x * x
arg :: Int
arg = 2
foo <^> arg -- valid, returns 4
arg <^> foo -- valid, returns 4
I have tried to accomplish that through type families, as follows:
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeFamilies, TypeOperators #-}
class Combine t1 t2 where
type Output t1 t2 :: *
(<^>) :: t1 -> t2 -> Output t1 t2
instance Combine (a->b) a where
type Output (a->b) a = b
f <^> x = f x
instance Combine a (a->b) where
type Output a a->b = b
x <^> f = f x
On this code, GHC throws a Conflicting family instance declarations. My guess is that the overlap GHC complains about occurs when type a->b and type a are the same. I don't know Haskell well enough, but I suspect that with recursive type definitions, one may be able to construct such a situation. I have a couple of questions:
Since this is a rather remote scenario that will never occur in my application (in particular not with foo and arg above), I was wondering if there was a way of specifying a dummy default instance to use in case of overlap? I have tried the different OVERLAPS and OVERLAPPING flags, but they didn't have any effect.
If not, is there a better way of achieving what I want?
Thanks!
This is a bad idea, in my view, but I'll play along.
A possible solution is to switch to functional dependencies. Usually I tend to avoid fundeps in favor of type families, but here they make the instances compile in a simple way.
class Combine t1 t2 r | t1 t2 -> r where
(<^>) :: t1 -> t2 -> r
instance Combine (a->b) a b where
f <^> x = f x
instance Combine a (a->b) b where
x <^> f = f x
Note that this class will likely cause problems during type inference if we use polymorphic functions. This is because, with polymorphic functions, the code can easily become ambiguous.
For instance id <^> id could pick any of the two instances. Above, melpomene already reported const <^> id being ambiguous as well.
The following is weakly related, but I want to share it anyway:
What about type families instead? I tried to experiment a bit, and I just discovered a limitation which I did not know. Consider the closed type family
type family Output a b where
Output (a->b) a = b
Output a (a->b) = b
The code above compiles, but then the type Output a (a->b) is stuck. The second equation does not get applied, as if the first one could potentially match.
Usually, I can understand this in some other scenarios, but here unifying
Output (a' -> b') b' ~ Output a (a -> b)
seems to fail since we would need a ~ (a' -> b') ~ (a' -> a -> b) which is impossible, with finite types. For some reason, GHC does not use this argument (does it pretend infinite types exist in this check? why?)
Anyway, this makes replacing fundeps with type families harder than it could be, it seems. I have no idea about why GHC accepts the fundeps code I posted, yet refuses the OP's code which is essentially the same thing, except using type families.
#chi is close; an approach using either FunDeps or Closed Type Families is possible. But the Combine instances are potentially ambiguous/unifiable just as much as the CTF Output equations.
When chi says the FunDep code is accepted, that's only half-true: GHC plain leads you down the garden path. It will accept the instances but then you find you can't use them/you get weird error messages. See the Users Guide at "potential for overlap".
If you're looking to resolve a potentially ambiguous Combine constraint, you might get an error suggesting you try IncoherentInstances (or INCOHERENT pragma). Don't do that. You have a genuinely incoherent problem; all that will do is defer the problem to somewhere else. It's always possible to avoid Incoherent -- providing you can rejig your instances (as follows) and they're not locked away in libraries.
Notice that because of the potential ambiguity, another Haskell compiler (Hugs) doesn't let you write Combine like that. It has a more correct implementation of Haskell's (not-well-stated) rules.
The answer is to use a sort of overlap where one instance is strictly more specific. You must first decide which you way you want to prefer in case of ambiguity. I'll choose function prefixed to argument:
{-# LANGUAGE UndecidableInstances, TypeFamilies #-}
instance {-# OVERLAPPING #-} (r ~ b)
=> Combine (a->b) a r where ...
instance {-# OVERLAPPABLE #-} (Combine2 t1 t2 r)
=> Combine t1 t2 r where
(<^>) = revApp
class Combine2 t1 t2 r | t1 t2 -> r where
revApp :: t1 -> t2 -> r
instance (b ~ r) => Combine2 a (a->b) r where
revApp x f = f x
Notice that the OVERLAPPABLE instance for Combine has bare tyvars, it's a catch-all so it's always matchable. All the compiler has to do is decide whether some wanted constraint is of the form of the OVERLAPPING instance.
The Combine2 constraint on the OVERLAPPABLE instance is no smaller than the head, so you need UndecidableInstances. Also beware that deferring to Combine2 will mean that if the compiler still can't resolve, you're likely to get puzzling error messages.
Talking of bare tyvars/"always matchable", I've used an additional trick to make the compiler work really hard to improve the types: There's bare r in the head of the instance, with an Equality type improvement constraint (b ~ r) =>. To use the ~, you need to switch on TypeFamilies even though you're not writing any type families.
A CTF approach would be similar. You need a catch-all equation on Output that calls an auxiliary type function. Again you need UndecidableInstances.

Class contraints for monads and monad functions

I am trying to write a new monad that only can contain a Num. When it fails, it returns 0 much like the Maybe monad returns Nothing when it fails.
Here is what I have so far:
data (Num a) => IDnum a = IDnum a
instance Monad IDnum where
return x = IDnum x
IDnum x >>= f = f x
fail :: (Num a) => String -> IDnum a
fail _ = return 0
Haskell is complaining that there is
No instance for (Num a) arising from a use of `IDnum'
It suggests that I add a add (Num a) to the context of the type signature for each of my monad functions, but I tried that it and then it complains that they need to work "forall" a.
Ex:
Method signature does not match class; it should be
return :: forall a. a -> IDnum a
In the instance declaration for `Monad IDnum'
Does anyone know how to fix this?
The existing Monad typeclass expects your type to work for every possible type argument. Consider Maybe: in Maybe a, a is not constrained at all. Basically you can't have a Monad with constraints.
This is a fundamental limitation of how the Monad class is defined—I don't know of any way to get around it without modifying that.
This is also a problem for defining Monad instances for other common types, like Set.
In practice, this restriction is actually pretty important. Consider that (normally) functions are not instances of Num. This means that we could not use your monad to contain a function! This really limits important operations like ap (<*> from Applicative), since that depends on a monad containing a function:
ap :: Monad m => m (a -> b) -> m a -> m b
Your monad would not support many common uses and idioms we've grown to expect from normal monads! This would rather limit its utility.
Also, as a side-note, you should generally avoid using fail. It doesn't really fit in with the Monad typeclass: it's more of a historic accident. Most people agree that you should avoid it in general: it was just a hack to deal with failed pattern matches in do-notation.
That said, looking at how to define a restricted monad class is a great exercise for understanding a few Haskell extensions and learning some intermediate/advanced Haskell.
Alternatives
With the downsides in mind, here are a couple of alternatives—replacements for the standard Monad class that do support restricted monads.
Constraint Kinds
I can think of a couple of possible alternatives. The most modern one would be taking advantage of the ConstraintKind extension in GHC, which lets you reify typeclass constraints as kinds. This blog post details how to implement a restricted monad using constraint kinds; once I've read it, I'll summarize it here.
The basic idea is simple: with ConstraintKind, we can turn our constrain (Num a) into a type. We can then have a new Monad class which contains this type as a member (just like return and fail are members) and allows use to overload the constraint with Num a. This is what the code looks like:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
module Main where
import Prelude hiding (Monad (..))
import GHC.Exts
class Monad m where
type Restriction m a :: Constraint
type Restriction m a = ()
return :: Restriction m a => a -> m a
(>>=) :: Restriction m a => m a -> (a -> m b) -> m b
fail :: Restriction m a => String -> m a
data IDnum a = IDnum a
instance Monad IDnum where
type Restriction IDnum a = Num a
return = IDnum
IDnum x >>= f = f x
fail _ = return 0
RMonad
There is an existing library on hackage called rmonad (for "restricted monad") which provides a more general typeclass. You could probably use this to write your desired monad instance. (I haven't used it myself, so it's a bit hard to say.)
It doesn't use the ConstraintKinds extension and (I believe) supports older versions of GHC. However, I think it's a bit ugly; I'm not sure that it's the best option any more.
Here's the code I came up with:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
import Prelude hiding (Monad (..))
import Control.RMonad
import Data.Suitable
data IDnum a = IDnum a
data instance Constraints IDnum a = Num a => IDnumConstraints
instance Num a => Suitable IDnum a where
constraints = IDnumConstraints
instance RMonad IDnum where
return = IDnum
IDnum x >>= f = f x
fail _ = withResConstraints $ \ IDnumConstraints -> return 0
Further Reading
For more details, take a look at this SO question.
Oleg has an article about this pertaining specifically to the Set monad, which might be interesting: "How to restrict a monad without breaking it".
Finally, there are a couple of papers you could also read:
The Constrained-Monad Problem
Generic Monadic Constructs for Embedded Languages
This answer will be brief, but here's another alternative to go along with Tikhon's. You can apply a codensity transformation to your type to basically get a free monad for it. Just use it (in the below code it's IDnumM) instead of your base type, then convert the final value to your base type at the end (in the below code, you would use runIDnumM). You can also inject your base type into the transformed type (in the below code, that would be toIDnumM).
A benefit of this approach is that it works with the standard Monad class.
data Num a => IDnum a = IDnum a
newtype IDnumM a = IDnumM { unIDnumM :: forall r. (a -> IDnum r) -> IDnum r }
runIDnumM :: Num a => IDnumM a -> IDnum a
runIDnumM (IDnumM n) = n IDnum
toIDnumM :: Num a => IDnum a -> IDnumM a
toIDnumM (IDnum x) = IDnumM $ \k -> k x
instance Monad IDnumM where
return x = IDnumM $ \k -> k x
IDnumM m >>= f = IDnumM $ \k -> m $ \x -> f x `unIDnumM` k
There is an easier way to do this. One can use multiple functions. First, write one in the Maybe monad. The Maybe monad returns Nothing upon failure. Second, write a function that returns the Just value if not Nothing or some safe value if Nothing. Third, write a function that composes those two functions.
This produces the desired result while being much easier to write and understand.

Associated Parameter Restriction using Functional Dependency

The function f below, for a given type 'a', takes a parameter of type 'c'. For different types 'a', 'c' is restricted in different ways. Concretely, when 'a' is any Integral type, 'c' should be allowed to be any 'Real' type. When 'a' is Float, 'c' can ONLY be Float.
One attempt is:
{-# LANGUAGE
MultiParamTypeClasses,
FlexibleInstances,
FunctionalDependencies,
UndecidableInstances #-}
class AllowedParamType a c | a -> c
class Foo a where
f :: (AllowedParamType a c) => c -> a
fIntegral :: (Integral a, Real c) => c -> a
fIntegral = error "implementation elided"
instance (Integral i, AllowedParamType i d, Real d) => Foo i where
f = fIntegral
For some reason, GHC 7.4.1 complains that it "could not deduce (Real c) arising from a use of fIntegral". It seems to me that the functional dependency should allow this deduction. In the instance, a is unified with i, so by the functional dependency, d should be unified with c, which in the instance is declared to be 'Real'. What am I missing here?
Functional dependencies aside, will this approach be expressive enough to enforce the restrictions above, or is there a better way? We are only working with a few different values for 'a', so there will be instances like:
instance (Integral i, Real c) => AllowedParamType i c
instance AllowedParamType Float Float
Thanks
A possibly better way, is to use constraint kinds and type families (GHC extensions, requires GHC 7.4, I think). This allows you to specify the constraint as part of the class instance.
{-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances, UndecidableInstances #-}
import GHC.Exts (Constraint)
class Foo a where
type ParamConstraint a b :: Constraint
f :: ParamConstraint a b => b -> a
instance Integral i => Foo i where
type ParamConstraint i b = Real b
f = fIntegral
EDIT: Upon further experimentation, there are some subtleties that mean that this doesn't work as expected, specifically, type ParamConstraint i b = Real b is too general. I don't know a solution (or if one exists) right now.
OK, this one's been nagging at me. given the wide variety of instances,
let's go the whole hog and get rid of any relationship between the
source and target type other than the presence of an instance:
{-# LANGUAGE OverlappingInstances, FlexibleInstances,TypeSynonymInstances,MultiParamTypeClasses #-}
class Foo a b where f :: a -> b
Now we can match up pairs of types with an f between them however we like, for example:
instance Foo Int Int where f = (+1)
instance Foo Int Integer where f = toInteger.((7::Int) -)
instance Foo Integer Int where f = fromInteger.(^ (2::Integer))
instance Foo Integer Integer where f = (*100)
instance Foo Char Char where f = id
instance Foo Char String where f = (:[]) -- requires TypeSynonymInstances
instance (Foo a b,Functor f) => Foo (f a) (f b) where f = fmap f -- requires FlexibleInstances
instance Foo Float Int where f = round
instance Foo Integer Char where f n = head $ show n
This does mean a lot of explicit type annotation to avoid No instance for... and Ambiguous type error messages.
For example, you can't do main = print (f 6), but you can do main = print (f (6::Int)::Int)
You could list all of the instances with the standard types that you want,
which could lead to an awful lot of repetition, our you could light the blue touchpaper and do:
instance Integral i => Foo Double i where f = round -- requires FlexibleInstances
instance Real r => Foo Integer r where f = fromInteger -- requires FlexibleInstances
Beware: this does not mean "Hey, if you've got an integral type i,
you can have an instance Foo Double i for free using this handy round function",
it means: "every time you have any type i, it's definitely an instance
Foo Double i. By the way, I'm using round for this, so unless your type i is Integral,
we're going to fall out." That's a big issue for the Foo Integer Char instance, for example.
This can easily break your other instances, so if you now type f (5::Integer) :: Integer you get
Overlapping instances for Foo Integer Integer
arising from a use of `f'
Matching instances:
instance Foo Integer Integer
instance Real r => Foo Integer r
You can change your pragmas to include OverlappingInstances:
{-# LANGUAGE OverlappingInstances, FlexibleInstances,TypeSynonymInstances,MultiParamTypeClasses #-}
So now f (5::Integer) :: Integer returns 500, so clearly it's using the more specific Foo Integer Integer instance.
I think this sort of approach might work for you, defining many instances by hand, carefully considering when to go completely wild
making instances out of standard type classes. (Alternatively, there aren't all that many standard types, and as we all know, notMany choose 2 = notIntractablyMany, so you could just list them all.)
Here's a suggestion to solve a more general problem, not yours specifically (I need more detail yet first - I promise to check later). I'm writing it in case other people are searching for a solution to a similar problem to you, I certainly was in the past, before I discovered SO. SO is especially great when it helps you try a radically new approach.
I used to have the work habit:
Introduce a multi-parameter type class (Types hanging out all over the place, so...)
Introduce functional dependencies (Should tidy it up but then I end up needing...)
Add FlexibleInstances (Alarm bells start ringing. There's a reason the compiler has this off by default...)
Add UndecidableInstances (GHC is telling you you're on your own, because it's not convinced it's up to the challenge you're setting it.)
Everything blows up. Refactor somehow.
Then I discovered the joys of type families (functional programming for types (hooray) - multi-parameter type classes are (a bit like) logic programming for types). My workflow changed to:
Introduce a type class including an associated type, i.e. replace
class MyProblematicClass a b | a -> b where
thing :: a -> b
thang :: b -> a -> b
with
class MyJustWorksClass a where
type Thing a :: * -- Thing a is a type (*), not a type constructor (* -> *)
thing :: a -> Thing a
thang :: Thing a -> a -> Thing a
Nervously add FlexibleInstances. Nothing goes wrong at all.
Sometimes fix things by using constraints like (MyJustWorksClass j,j~a)=> instead of (MyJustWorksClass a)=> or (Show t,t ~ Thing a,...)=> instead of (Show (Thing a),...) => to help ghc out. (~ essentially means 'is the same type as')
Nervously add FlexibleContexts. Nothing goes wrong at all.
Everything works.
The reason "Nothing goes wrong at all" is that ghc calculates the type Thing a using my type function Thang rather than trying to deduce it using a merely a bunch of assertions that there's a function there and it ought to be able to work it out.
Give it a go! Read Fun with Type Functions before reading the manual!

Resources