How to get rid of this ambiguity? - haskell

I am pretty sure this has been asked before, however I was unable to find the right answer:
I tried to eliminate the ambiguity in the following exemplary code snippet:
{-# LANGUAGE MultiParamTypeClasses #-}
class FooBar a b where
foo :: a -> a
foo = id
bar :: a -> a
bar = foo -- ERROR AT THIS LINE
I get an error message like so:
Ambiguous type variable `b0' in the constraint:
(FooBar a b0) arising from a use of `foo'
Probable fix: add a type signature that fixes these type variable(s)
In the expression: foo
In an equation for `bar': bar = foo
which is understandable. Note however, that I'm actually unable to follow the compiler's advice and fix the type variable in question: foo doesn't contain b type variable in its type signature. Also this doesn't work:
bar = (foo :: FooBar a b => a -> a) -- ERROR, the same error message
Not even with -XScopedTypeVariables enabled.
How to tell GHC which FooBar to use? Is it even possible?
EDIT
Following some answers: yes, I've heard about both functional dependencies and associated types.
As to functional dependencies - I am looking for a way to explicitly inform GHC which instance to use (as opposed to asking it to derive the correct type all by itself).
As to both - in the real world example that this one comes from, I actually need both of the parameters a and b to be independent.
Again: I know this example is extremely silly, I know b is not used in the body of the type class, which makes no sense. This is an extreme simplification of a real world example, that actually does make sense. The real use-case involves "substitutability" of types a using types b and then "unifiability" of types a and b using types c and unfortunately is much longer.
EDIT(2)
Okay sorry. I think you convinced me after all that I have to refactor the code in order not to have any ill-defined functions (i.e. ones that don't contain all the independent types in their type signatures). Talking to you really helped me think this thing though. Appreciated.

Your class is ill-defined even if you remove bar completely from the class. Let's just assume you have the following class:
class FooBar a b
where
foo :: a -> a
foo = id
Suppose now you would like to use foo outside the definition of this class.
e = .... foo x .....
GHC will complain with a similar error message than yours, that it can't find a type for b. Simply because your code doesn't supply such a type. Your type class declaration says every pair of types a and b might get an instance. So, even when a is fixed in a call of foo there are still arbitrary many possible instances to select from.
A functional dependency a -> b would solve that problem, because it states: Given a type a there may be only one instance of Foobar a b. An associated type avoids the problem by not using multi-parameter type classes.
regarding the OP's EDIT:
If you insist on having two type parameters. Then every method's signature of the type class has to contain every type variable of the class. There is no way around it.

If you introduce a functional dependency, class FooBar a b | a -> b where, that would settle it, but without that (or associated types), I think it is impossible to resolve the instance to use.
Oh, one way, but kind of ugly: introduce a dummy parameter of type b
class FooBar a b where
foo' :: b -> a -> a
foo' _ = id
bar' :: b -> a -> a
bar' b = foo b

Related

Haskell: Defining a variable inside a typeclass

I am new to Haskell and I stumbled upon this problem while playing around with classes.
So basically instead of defining functions inside a class, I want to define variables. In my case I'm defining a variable maxvalue inside the class Maxable. This worked just fine with Int. Now assuming a type a is an instance of Maxable, I want to define instance Maxable (Maybe a), which you can see in the third block of my code didn't work.
class Maxable a where
maxvalue :: a
-- This works fine
instance Maxable Int where
maxvalue = 2147483647
-- Error: Could not deduce (Maxable a1) arising from a use of ‘maxvalue’
instance Maxable a => Maxable (Maybe a) where
maxvalue = maxvalue :: a
What should I replace maxvalue = maxvalue :: a with so that "(Maybe a).maxvalue == a.maxvalue" ?
You're actually really close to the right answer!
First, to actually solve the problem, you need to recognize that in your Maxable instance for Maybe a, the type of maxvalue needs to be of type Maybe a. However, in your definition, you're making it of type a. So, how do you turn a value of type a into a value of type Maybe a? You use the Just constructor. In short, you can write:
instance Maxable a => Maxable (Maybe a) where
maxvalue = Just maxvalue
As it turns out, GHC is smart enough to use the right maxvalue without you even needing to use the :: a annotation.
But, what about that error you got? Why did it tell you something about Maxable a1? The problem that GHC is pointing out comes from the fact that you used the explicit type signature maxvalue :: a in your definition. By default, GHC does not scope type variables, so GHC didn't know that you wanted to use the same a there that you're using in your instance head. GHC assumed you just wanted a new, fresh type variable, which, internally, it decided to call a1. Then, it got confused at you because, while it knows that a is Maxable (because you said so in the instance context), it doesn't know that a1 is Maxable.
To get a better error message in this case, you can enable the GHC extension ScopedTypeVariables by adding
{-# LANGUAGE ScopedTypeVariables #-}
to the top of your file. If you run your current code with this language extension, you'll get a different error, with GHC complaining that a is not equal to Maybe a. As I stated above, this can be solved by using the Just constructor.

Universally quantified (or polymorphic) type class instances

Is it possible to define a generic type class instance parameterized by a type a in Haskell?
For example:
data Box a = Box a deriving Show
class Boxable a where
create :: a -> Box a
-- pseudo syntax here
instance forall a . Boxable a where
create = Box
If no, why not?
I am aware of the fact that this example is rather simple and "useless". I just want to know whether this is theoretically possible, not whether its practically relevant.
Your code is literally legal Haskell, nothing “pseudo syntax” about it. It's not quite Haskell98, but with two very harmless syntactic extensions it does compile:
{-# LANGUAGE ExplicitForall, FlexibleInstances #-}
data Box a = Box a deriving Show
class Boxable a where
create :: a -> Box a
instance forall a . Boxable a where
create = Box
The -XExplicitForall† is required for the explicit forall (duh), but actually you don't even need this because Haskell type variables are by default universally quantified:
{-# LANGUAGE FlexibleInstances #-}
instance Boxable a where
create = Box
Except, like chepner already commented this doesn't really make sense, because now create behaves just like a regular parametric function without any typeclass needed:
create' :: a -> Box a
create' = Box
That said, such once-and-for-all instances can actually be useful, if you constrain them with some superclass:
class Foo a
class Bar a
class (Foo a, Bar a) => FooBar a
instance (Foo a, Bar a) => FooBar a
Now if you mention FooBar (someComplicatedType) in a function's constraints, it has the same effect as writing out (Foo (someComplicatedType), Bar (someComplicatedType), which can significantly de-clunk your code and error messages and also make your projects more future-safe, because you can add or remove superclasses to FooBar without changing the signatures of all the functions that have this constraint.
(A very similar thing can be achieved with -XConstraintKinds as the arguably more straightforward constraint synonym type FooBar a = (Foo a, Bar a), but this brings in the well-known problem that type isn't really an encapsulation at all but can be unravelled by the compiler at any time, which isn't normally much of a problem except it leads to much more confusing type error messages.)
†You won't find -XExplicitForall itself very often in Haskell files, because it's only really needed as part of either -XScopedTypeVariables or -XRankNTypes, both of which are common and enable the forall keyword, or ∀ as I prefer to write it (which additionally requires -XUnicodeSyntax).

DeriveAnyClass vs Empty Instance

Suppose that I have this type family that throws a custom type error during compile time if the type passed to it is not a record:
type family IsRecord (a :: Type) where
...
Now I have this type class that has methods with default implementations, but requires that the type is a record, by adding the IsRecord constraint:
class IsRecord a => Foo a where
foo :: Text
foo = "foo"
When trying to use it incorrectly, if we use it as a regular instance with a type that is not a record, it successfully fails to compile:
data Bar = Bar
instance Foo Bar -- error: Bar is not a record
But if I enable -XDeriveAnyClass and add it to the deriving clause, this doesn't fail to compile, ignoring completely the constraint:
data Bar = Bar
deriving (Foo)
I understand that DeriveAnyClass generates an empty instance declaration, which is what I'm doing on the first example, but still it doesn't throw the error. What's going on?
I'm using GHC 8.6.4
Wow! I was going to mark this as a duplicate of What is the difference between DeriveAnyClass and an empty instance?, but it seems the behavior of GHC has changed since that question was asked and answered!
Anyway, if you ask -- either with :i inside ghci or with -ddump-deriv before starting ghci -- what the compiler has done, it's clear what the difference is in your case:
> :i Bar
data Bar = Bar -- Defined at test.hs:15:1
instance IsRecord Bar => Foo Bar -- Defined at test.hs:16:13
Indeed, if you change the non-DeriveAnyClass version of your code to match, writing
instance IsRecord Bar => Foo Bar
instead of
instance Foo Bar
everything works fine. The details of how this instance context was chosen seem a bit complicated; you can read what the GHC manual has to say about it here, though I suspect the description there is either not quite precise or not complete, as I don't get the same answer the compiler does here if I strictly follow the rules stated at the documentation. (I suspect the true answer is that it writes the instance first, then just does the usual type inference thing and copies any constraints it discovers in that way into the instance context.)

How to introspect an Haskell file to get the types of its definitions

I have many files that must be processed automatically. Each file holds the response of one student to an exercise which asks the student to give definitions for some functions given a type for each function.
My idea is to have an Haskell script that loads each student file, and verifies if each function has the expected type.
A constraint is that the student files are not defined as modules.
How can I do this?
My best alternative so far is to spawn a GHCi process that will read stdin from a "test file" with GHCi commands, for example:
:load student1.hs
:t g
... and so on ...
then parse the returned output from GHCi to find the types of the functions in the student file.
Is there another clean way to load an arbitrary Haskell file and introspect its code?
Thanks
Haskell does not save type information at runtime. In Haskell, types are used for pre-runtime type checking at the static analysis phase and are later erased. You can read more about Haskell's type system here.
Is there a reason you want to know the type of a function at runtime? maybe we can help with the problem itself :)
Edit based on your 2nd edit:
I don't have a good solution for you, but here is one idea that might work:
Run a script that for each student module will:
Take the name of the module and produce a file Test.hs:
module Test where
import [module-name]
test :: a -> b -> [(b,a)]
test = g
run ghc -fno-code Test.hs
check the output does not contain type errors
write results into a log file
I think if you have a dynamically determined number of .hs files, which you need to load, parse and introspect, you could/should use the GHC API instead.
See for example:
Using GHC API to compile Haskell sources to CORE and CORE to binary
https://mail.haskell.org/pipermail/haskell-cafe/2009-April/060705.html
These might not be something you can use directly — and I haven't done anything like this myself so far either — but these should get you started.
See also:
https://wiki.haskell.org/GHC/As_a_library
https://hackage.haskell.org/package/hint
The closest Haskell feature to that is Data.Typeable.typeOf. Here's a GHCi session:
> import Data.Typeable
> typeOf (undefined :: Int -> Char)
Int -> Char
> typeOf (undefined :: Int -> [Char])
Int -> [Char]
> typeOf (undefined :: Int -> Maybe [Char])
Int -> Maybe [Char]
> :t typeOf
typeOf :: Typeable a => a -> TypeRep
Under the hood, the Typeable a constraint forces Haskell to retain some type tags until runtime, so that they can be retrieved by typeOf. Normally, no such tags exist at runtime. The TypeRep type above is the type for such tags.
That being said, having such information is almost never needed in Haskell. If you are using typeOf to implement something, you are likely doing it wrong.
If you are using that to defer type checks to run time, when they could have been performed at compile time, e.g. using a Dynamic-like type for everything, then you are definitely doing it wrong.
If the function is supposed to be exported with a specific name, I think probably the easiest way would be to just write a test script that calls the functions and checks they return the right results. If the test script doesn't compile, the student's submission is incorrect.
The alternative is to use either the GHC API (kinda hard), or play with Template Haskell (simpler, but still not that simple).
Yet another possibility is to load the student's code into GHCi and use the :browse command to dump out everything that's exported. You can then grep for the term you're interested in. That should be quite easy to automate.
There's a catch, however: foo :: x -> x and foo :: a -> a are the same type, even though textually they don't match at all. You might contemplate trying to normalise the variable names, but it's worse: foo :: Int -> Int and foo :: Num x => x -> x don't look remotely the same, yet one type is an instance of the other.
...which I guess means I'm saying that my answer is bad? :-(

Simple Haskell Instance Question

I'm trying different data structures for implementing Prim's algorithm. So I made a class to abstract what I want to do:
class VertexContainer a where
contains :: a -> Vertex -> Bool
insert :: a -> WeightedEdge -> a
numVertices :: a -> Int
Now I want to use a heap (from Data.Heap) as my vertex container. But I can't for the life of me figure out the syntax. As you can see from the insert declaration, the container can only hold WeightedEdges, which are a data type. So I tried:
instance VertexContainer (Heap MinPolicy WeightedEdge) where
contains _ _ = True
It tells me it's an illegal type synonym. I've tried various other permutations, and none of them seem to work. Can anyone help me?
If you read the entire error message you'll find that it tells you how to be able to use a type synonym in an instance declaration, namely by using the language extension TypeSynonymInstances. E.g., you can pass -XTypeSynonymInstances on the command line.
I got it working by wrapping this into a newtype. Considered ugly. I guess you have to wait for one of the Haskell gurus to answer this.

Resources