Associated Parameter Restriction using Functional Dependency - haskell

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!

Related

Constraint on method depends on instances in scope?

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.

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.

Resolving type ambiguities using available class instances

Given the following code:
import Data.Word
data T = T deriving (Eq, Show)
class C a where f :: a -> ()
instance C T where f _ = ()
instance C Word16 where f _ = ()
main = return $ f 0x16
GHC complains that it can't infer what the type for the literal 0x16 should be with the error:
No instance for (Num a0) arising from the literal ‘22’
The type variable ‘a0’ is ambiguous
It is easy to see why this would be -- Haskell allows numeric literals to be of any type which has an instance of Num, and here we can't disambiguate what the type for the literal 0x16 (or 22) should be.
It's also clear as a human reading this what I intended to do -- there is only one available instance of the class C which satisfies the Num constraint, so obviously I intended to use that one so 0x16 should be treated as a Word16.
There are two ways that I know to fix it: Either annotate the literal with its type:
main = return $ f (0x16 :: Word16)
or define a function which essentially does that annotation for you:
w16 x = x :: Word16
main = return $ f (w16 0x16)
I have tried a third way, sticking default (Word16) at the top of the file in the hope that Haskell would pick that as the default type for numeric literals, but I guess I'm misunderstanding what the default keyword is supposed to do because that didn't work.
I understand that typeclasses are open, so just because you can make the assumption in the context quoted above that Word16 is the only numeric instance of C that may not hold in some other module. But my question is: is there some mechanism by which I can assume/enforce that property, so that it is possible to use f and have Haskell resolve the type of its numeric argument to Word16 without explicit annotations at the call site?
The context is that I am implementing an EDSL, and I would rather not have to include manual type hints when I know that my parameters will either be Word16 or some other non-numeric type. I am open to a bit of dirty types/extensions abuse if it makes the EDSL feel more natural! Although if solutions do involve the naughty pragmas I'd definitely appreciate hints on what I should be wary about when using them.
Quick solution with "naughty pragmas" with GHC 7.10:
{-# LANGUAGE TypeFamilies, FlexibleInstances #-}
class C a where f :: a -> ()
instance C T where f _ = ()
instance {-# INCOHERENT #-} (w ~ Word16) => C w where f _ = ()
And with GHC 7.8:
{-# LANGUAGE TypeFamilies, FlexibleInstances, IncoherentInstances #-}
class C a where f :: a -> ()
instance C T where f _ = ()
instance (w ~ Word16) => C w where f _ = ()
Here, GHC essentially picks an arbitrary most specific instance that remains after trying to unify the instances heads and constraints.
You should only use this if
You have a fixed set of instances and don't export the class.
For all use cases of the class method, there is a single possible most specific instance (given the constraints).
Many people advise against ever using IncoherentInstances, but I think it can be quite fun for DSL-s, if we observe the above considerations.
For anybody else wondering about default (I know I was!)
https://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-750004.3
Quoting section 4.3.4:
In situations where an ambiguous type is discovered, an ambiguous type variable, v, is defaultable if:
v appears only in constraints of the form C v, where C is a class, and
at least one of these classes is a numeric class, (that is, Num or a subclass of Num), and
all of these classes are defined in the Prelude or a standard library.
So that explains why your default clause is being completely ignored; C is not a standard library type-class.
(As to why this is the rule… can't help you there. Presumably to avoid breaking arbitrary user-defined code.)

Constraint Inference from Instances

Consider the following:
{-# LANGUAGE FlexibleContexts #-}
module Foo where
data D a = D a
class Foo b
instance (Num a) => Foo (D a)
f :: (Foo (D a)) => a -> a
f x = x+1
GHC complains that it cannot deduce Num a in f. I would like this constraint to be inferred from the (non-overlapping) instance of Foo for D a.
I know I could use a GADT for D and add the constraint Num a there, but I'm hoping to not have to pollute the constructor for D with lots of unnecessary constraints. Is there any hope of this ever happening, and is it possible now?
I am guessing this would break for overlapping instances, and therefore is not inferred in general. That is, you could have
{-# LANGUAGE OverlappingInstances #-}
...
instance (Num a) => Foo (D a)
instance Foo (D Bool)
and then your desired inference would certainly not be sound.
EDIT: Looking more closely at the documentation, it is possible to have
{-# LANGUAGE FlexibleContexts #-}
module Foo where
data D a = D a
class Foo b
instance (Num a) => Foo (D a)
f :: (Foo (D a)) => a -> a
f x = x+1
and then in a separate file:
{-# LANGUAGE OverlappingInstances #-}
module Bar where
import Foo
instance Foo Bool
test = f True
That is, the documentation implies only one of the modules defining the two instances needs to have the OverlappingInstances flag, so if Foo.f were definable as this, you could make another module Bar break type safety completely. Note that with GHC's separate compilation, f would be compiled completely without knowledge of the module Bar.
The arrow => is directional. It means that if Num a holds then Foo (D a). It does not mean that if Foo (D a) holds then Num a holds.
The knowledge that there are (and will never be) any overlapping instances for Foo (D a) should imply that the reverse implication is also true, but (a) GHC doesn't know this and (b) GHC's instance machinery is not set up to use this knowledge.
To actually compile functions that use type classes, it's not enough for GHC to merely prove that a type must be an instance of a class. It has to actually come up with a specific instance declaration that provides definitions of the member functions. We need a constructive proof, not just an existence proof.
To identify an instance of class C, it can either reuse one that will be chosen by the caller of the function being compiled, or it must know the types involved concretely enough to select a single instance from those available. The function being compiled will only be passed an instance for C if it has a constraint for C; otherwise the function must be sufficiently monomorphic that it can only use a single instance.
Considering your example specifically, we can see that f has a constraint for Foo (D a), so we can rely on the caller providing that for us. But the caller isn't going to give us an instance for Num a. Even if you presume that we know from the Num a constraint on Foo (D a) that there must be such an instance out there somewhere, we have no idea what a is, so which definition of + should we invoke? We can't even call another function that works for any Num a but is defined outside the class, because they will all have the Num a constraint and thus expect us to identify an instance for them. Knowing that there is an instance without having having the instance is just not useful.
It isn't at all obvious, but what you're actually asking GHC to do is to do a runtime switch on the type a that arrives at runtime. This is impossible, because we're supposed to be emitting code that works for any type in Num, even types that don't exist yet, or whose instances don't exist yet.
A similar idea that does work is when you have a constraint on the class rather than on the instance. For example:
class Num a => Foo a
f :: Foo a => a -> a
f x = x + 1
But this only works because we know that all Foo instances must have a corresponding Num instance, and thus all callers of a function polymorphic in Foo a know to also select a Num instance. So even without knowing the particular a in order to select a Num instance, f knows that its caller will also provide a Num instance along with the Foo instance.
In your case, the class Foo knows nothing about Num. In other examples Num might not even be defined in code accessible to the module where the class Foo is defined. It's the class that sets the required information that has to be provided to call a function that is polymorphic in the type class, and those polymorphic functions have to be able to work without any knowledge specific to a certain instance.
So the Num a => Foo (D a) instance can't store the Num instance - indeed, the instance definition is also polymorphic in a, so it's not able to select a particular instance to store even if there was space! So even though f might be able to know that there is a Num a instance from Foo (D a) (if we presume certain knowledge that no overlapping could ever be involved), it still needs a Num a constraint in order to require its callers to select a Num instance for it to use.

How can I use restricted constraints with GADTs?

I have the following code, and I would like this to fail type checking:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
import Control.Lens
data GADT e a where
One :: Greet e => String -> GADT e String
Two :: Increment e => Int -> GADT e Int
class Greet a where
_Greet :: Prism' a String
class Increment a where
_Increment :: Prism' a Int
instance Greet (Either String Int) where
_Greet = _Left
instance Increment (Either String Int) where
_Increment = _Right
run :: GADT e a -> Either String Int
run = go
where
go (One x) = review _Greet x
go (Two x) = review _Greet "Hello"
The idea is that each entry in the GADT has an associated error, which I'm modelling with a Prism into some larger structure. When I "interpret" this GADT, I provide a concrete type for e that has instances for all of these Prisms. However, for each individual case, I don't want to be able to use instances that weren't declared in the constructor's associated context.
The above code should be an error, because when I pattern match on Two I should learn that I can only use Increment e, but I'm using Greet. I can see why this works - Either String Int has an instance for Greet, so everything checks out.
I'm not sure what the best way to fix this is. Maybe I can use entailment from Data.Constraint, or perhaps there's a trick with higher rank types.
Any ideas?
The problem is you're fixing the final result type, so the instance exists and the type checker can find it.
Try something like:
run :: GADT e a -> e
Now the result type can't pick the instance for review and parametricity enforces your invariant.

Resources