Can I parameterise the empty constraint type? - haskell

I have a class for queues which allows the instance to define the constraints it places on the elements. For example, a priority queue requires its elements to be orderable:
{-# LANGUAGE MultiParamTypeClasses, ConstraintKinds, FunctionalDependencies #-}
class Queue q c | q -> c where
empty :: q a
qpop :: c a => q a -> Maybe (a, q a)
qpush :: c a => a -> q a -> q a
data PriorityQueue a = ...
instance Queue PriorityQueue Ord where
...
This works a charm: inside the instance declaration for PriorityQueue I can operate on elements of the queue using members of Ord such as (>).
I've got stuck trying to define a queue which places no requirements on its elements:
newtype LIFO a = LIFO [a]
instance Queue LIFO () where
empty = LIFO []
qpop (LIFO []) = Nothing
qpop (LIFO (x:xs)) = Just (x, LIFO xs)
qpush x (LIFO xs) = LIFO $ x:xs
This fails, with the following error message from GHC:
The second argument of `Queue' should have kind `* -> Constraint',
but `()' has kind `*'
In the instance declaration for `Queue LIFO ()'
This error message makes sense to me. Eq accepts a type parameter (we typically write Eq a => ...) whereas () has no parameters - it's a plain old kind mismatch.
I had a crack at writing a type function which ignores its second argument, which would allow me to write instance Queue LIFO (Const ()):
{-# LANGUAGE TypeFamilies, KindSignatures, PolyKinds #-}
type family Const a b :: k -> k2 -> k
type instance Const a b = a
I find this interaction of type families and kind polymorphism quite beautiful, so I was rather disappointed when it didn't work (I really thought it would!):
Expecting two more arguments to `a'
The first argument of `Const' should have kind `*',
but `a' has kind `k0 -> k1 -> k0'
In the type `a'
In the type instance declaration for `Const'
I have a feeling this last example is something stupid like a syntax mistake (I'm new to type families). How can I write a Constraint which doesn't place any restrictions on its argument?

This should work:
class NoConstraint a where
instance NoConstraint a where
instance Queue LIFO NoConstraint where
...
The above defines a constraint which is satisfied by all types. As such, the obligations c a where c = NoConstraint can always be discharged.
Also, since there are no members in that class, it should have zero (or nearly zero) run-time cost.
The "constraint" () you are trying to use is not seen as an empty constraint set by GHC, but as the unit type () :: *. This causes Const () :: k2 -> *, which triggers the kind error.
If you do not want to use a custom class, you might try e.g. Const (Eq ()) or Const (Num Int), which have the right kind k2 -> Constraint. I do not recommend this, though, since I find it less readable than using a custom class.
(This requires to enable some extensions, as Benjamin Hodgson points out below in a comment.)

Related

Using a default implementation of typeclass method to omit an argument

I want to be able to define a (mulit-parameter-) typeclass instance whose implementation of the class's method ignores one of its arguments. This can be easily done as follows.
instance MyType MyData () where
specific _ a = f a
As I'm using this pattern in several places, I tried to generalize it by adding a specialized class method and adequate default implementations. I came up with the following.
{-# LANGUAGE MultiParamTypeClasses, AllowAmbiguousTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
class MyType a b where
specific :: b -> a -> a
specific = const dontCare
dontCare :: a -> a
dontCare = specific (undefined :: b)
{-# MINIMAL specific | dontCare #-}
This however yields the error Could not deduce (MyType a b0) arising from a use of ‘dontCare’ [..] The type variable ‘b0’ is ambiguous. I don't see why the latter should be the case with the type variable b being scoped from the class signature to the method declaration. Can you help me understand the exact problem that arises here?
Is there another reasonable way to achieve what I intended, namely to allow such trimmed instances in a generic way?
The problem is in the default definition of specific. Let's zoom out for a second and see what types your methods are actually given, based on your type signatures.
specific :: forall a b. MyType a b => b -> a -> a
dontCare :: forall a b. MyType a b => a -> a
In the default definition of specific, you use dontCare at type a -> a. So GHC infers that the first type argument to dontCare is a. But nothing constrains its second type argument, so GHC has no way to select the correct instance dictionary to use for it. This is why you ended up needing AllowAmbiguousTypes to get GHC to accept your type signature for dontCare. The reason these "ambiguous" types are useful in modern GHC is that we have TypeApplications to allow us to fix them. This definition works just fine:
class MyType a b where
specific :: b -> a -> a
specific = const (dontCare #_ #b)
dontCare :: a -> a
dontCare = specific (undefined :: b)
{-# MINIMAL specific | dontCare #-}
The type application specifies that the second argument is b. You could fill in a for the first argument, but GHC can actually figure that one out just fine.

Is this use of GADTs fully equivalent to existential types?

Existentially quantified data constructors like
data Foo = forall a. MkFoo a (a -> Bool)
| Nil
can be easily translated to GADTs:
data Foo where
MkFoo :: a -> (a -> Bool) -> Foo
Nil :: Foo
Are there any differences between them: code which compiles with one but not another, or gives different results?
They are nearly equivalent, albeit not completely so, depending on which extensions you turn on.
First of all, note that you don't need to enable the GADTs extension to use the data .. where syntax for existential types. It suffices to enable the following lesser extensions.
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE ExistentialQuantification #-}
With these extensions, you can compile
data U where
U :: a -> (a -> String) -> U
foo :: U -> String
foo (U x f) = f x
g x = let h y = const y x
in (h True, h 'a')
The above code also compiles if we replace the extensions and the type definition with
{-# LANGUAGE ExistentialQuantification #-}
data U = forall a . U a (a -> String)
The above code, however, does not compile with the GADTs extension turned on! This is because GADTs also turns on the MonoLocalBinds extension, which prevents the above definition of g to compile. This is because the latter extension prevents h to receive a polymorphic type.
From the documentation:
Notice that GADT-style syntax generalises existential types (Existentially quantified data constructors). For example, these two declarations are equivalent:
data Foo = forall a. MkFoo a (a -> Bool)
data Foo' where { MKFoo :: a -> (a->Bool) -> Foo' }
(emphasis on the word equivalent)
The latter isn't actually a GADT - it's an existentially quantified data type declared with GADT syntax. As such, it is identical to the former.
The reason it's not a GADT is that there is no type variable that gets refined based on the choice of constructor. That's the key new functionality added by GADTs. If you have a GADT like this:
data Foo a where
StringFoo :: String -> Foo String
IntFoo :: Int -> Foo Int
Then pattern-matching on each constructor reveals additional information that can be used inside the matching clause. For instance:
deconstructFoo :: Foo a -> a
deconstructFoo (StringFoo s) = "Hello! " ++ s ++ " is a String!"
deconstructFoo (IntFoo i) = i * 3 + 1
Notice that something very interesting is happening there, from the point of view of the type system. deconstructFoo promises it will work for any choice of a, as long as it's passed a value of type Foo a. But then the first equation returns a String, and the second equation returns an Int.
This is what you cannot do with a regular data type, and the new thing GADTs provide. In the first equation, the pattern match adds the constraint (a ~ String) to its context. In the second equation, the pattern match adds (a ~ Int).
If you haven't created a type where pattern-matching can cause type refinement, you don't have a GADT. You just have a type declared with GADT syntax. Which is fine - in a lot of ways, it's a better syntax than the basic data type syntax. It's just more verbose for the easiest cases.

Why do Haskell's scoped type variables not allow binding of type variables in pattern bindings?

I noticed that GHC's ScopedTypeVariables is able to bind type variables in function patterns but not let patterns.
As a minimal example, consider the type
data Foo where Foo :: Typeable a => a -> Foo
If I want to gain access to the type inside a Foo, the following function does not compile:
fooType :: Foo -> TypeRep
fooType (Foo x) =
let (_ :: a) = x
in typeRep (Proxy::Proxy a)
But using this trick to move the type variable binding to a function call, it works without issue:
fooType (Foo x) =
let helper (_ :: a) = typeRep (Proxy::Proxy a)
in helper x
Since let bindings are actually function bindings in disguise, why aren't the above two code snippets equivalent?
(In this example, other solutions would be to create the TypeRep with typeOf x, or bind the variable directly as x :: a in the top-level function. Neither of those options are available in my real code, and using them doesn't answer the question.)
The big thing is, functions are case expressions in disguise, not let expressions. case matching and let matching have different semantics. This is also why you can't match a GADT constructor that does type refinement in a let expression.
The difference is that case matches evaluate the scrutinee before continuing, whereas let matches throw a thunk onto the heap that says "do this evaluation when the result is demanded". GHC doesn't know how to preserve locally-scoped types (like a in your example) across all the potential ways laziness may interact with them, so it just doesn't try. If locally-scoped types are involved, use a case expression such that laziness can't become a problem.
As for your code, ScopedTypeVariables actually provides you a far more succinct option:
{-# Language ScopedTypeVariables, GADTs #-}
import Data.Typeable
import Data.Proxy
data Foo where
Foo :: Typeable a => a -> Foo
fooType :: Foo -> TypeRep
fooType (Foo (x :: a)) = typeRep (Proxy :: Proxy a)

Haskell Ambiguous type error

I have the following definitions
{-# LANGUAGE MultiParamTypeClasses,
FunctionalDependencies,
FlexibleInstances,
FlexibleContexts #-}
import qualified Data.Map as M
class Graph g n e | g -> n e where
empty :: g -- returns an empty graph
type Matrix a = [[a]]
data MxGraph a b = MxGraph { nodeMap :: M.Map a Int, edgeMatrix :: Matrix (Maybe b) } deriving Show
instance (Ord n) => Graph (MxGraph n e) n e where
empty = MxGraph M.empty [[]]
When I try to call empty I get an ambiguous type error
*Main> empty
Ambiguous type variables `g0', `n0', `e0' in the constraint: ...
Why do I get this error? How can I fix it?
You are seeing this type error because Haskell is not provided with sufficient information to know the type of empty.
Any attempt to evaluate an expression though requires the type. The type is not defined yet because the instance cannot be selected yet. That is, as the functional dependency says, the instance can only be selected if type parameter g is known. Simply, it is not known because you do not specify it in any way (such as with a type annotation).
The type-class system makes an open world assumption. This means that there could be many instances for the type class in question and hence the type system is conservative in selecting an instance (even if currently there is only one instance that makes sense to you, but there could be more some other day and the system doesn't want to change its mind just because some other instances get into scope).

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