Ambiguous type variable 'blah' in the constraint... how to fix? - haskell

I'm trying to write a simple ray-tracer in Haskell. I wanted to define a typeclass representing the various kinds of surfaces available, with a function to determine where a ray intersects them:
{-# LANGUAGE RankNTypes #-}
data Vector = Vector Double Double Double
data Ray = Ray Vector Vector
class Surface s where
intersections :: s -> Ray -> [Vector]
-- Obviously there would be some concrete surface implementations here...
data Renderable = Renderable
{ surface :: (Surface s) => s
, otherStuff :: Int
}
getRenderableIntersections :: Renderable -> Ray -> [Vector]
getRenderableIntersections re ra = intersections (surface re) ra
However this gives me the error:
Ambiguous type variable 's' in the constraint:
'Surface'
arising from a use of 'surface'
(The actual code is more complex but I've tried to distill it to something simpler, while keeping the gist of what I'm trying to achieve).
How do I fix this? Or alternatively, given that I come from a standard OO background, what am I fundamentally doing wrong?

Please don't use existential types for this! You could, but there would be no point.
From a functional standpoint you can drop this typeclass notion of Surface entirely. A Surface is something that maps a Ray to a list of Vectors, no? So:
type Surface = Ray -> [Vector]
data Renderable = Renderable
{ surface :: Surface
, otherStuff :: Int
}
Now if you really want, you can have a ToSurface typeclass essentially as you gave:
class ToSurface a where
toSurface :: a -> Surface
But that's just for convenience and ad-hoc polymorphism. Nothing in your model requires it.
In general, there are a very few use cases for existentials, but at least 90% of the time you can substitute an existential with the functions it represents and obtain something cleaner and easier to reason about.
Also, even though it may be a tad too much for you to take in, and the issues don't exactly match, you might find useful some of Conal's writing on denotational design: http://conal.net/blog/posts/thoughts-on-semantics-for-3d-graphics/

In your getRenderableIntersections function you call surface. There is no way for the interpreter to figure out what instance of the class Surface you want to use. If you have two such instances:
instance Surface SurfaceA where
-- ...
instance Surface SurfaceB where
-- ...
How can the interpreter determine the type of surface?
The way you defined Renderable means there is a function surface :: Surface s => Renderable -> s.
Try creating an instance Surface SurfaceA and asking the following type query (given a simple constructor SurfaceA):
> :t surface (Renderable SurfaceA 0) -- What's the type of the expression?
So, what type is this expression? I bet you're expecting SurfaceA. Wrong. Take the type of surface. It takes a Renderable argument and we're passing it a Renderable argument. What is left after that? Surface s => s. That's the type of that expression. We still don't know what type does s represent.
If you want the type to be SurfaceA you need to change your code so it becomes something like surface :: Surface s => Renderable s -> s. This way what s is can be determined, because it is the same s used in Renderable.
EDIT: As suggested by #mokus, you could also try the ExistentialTypes extension. It allows "hiding" away type parameters on the right side of a type declaration.
data Renderable = forall s. Surface s => Renderable
{ surface :: s
, otherStuff :: Int
}
The HaskellWiki page I linked to above even has an example very similar to what you want to do.
EDIT: (By #stusmith) - For the record, I'm including code below which compiles based on these suggestions here. However I've accepted the answer which I think shows a better way of approaching things.
{-# LANGUAGE ExistentialQuantification #-}
data Vector = Vector Double Double Double
data Ray = Ray Vector Vector
class Surface_ s where
intersections :: s -> Ray -> [Vector]
data Surface = forall s. Surface_ s => Surface s
instance Surface_ Surface where
intersections (Surface s) ra = intersections s ra
data Renderable = Renderable
{ surface :: Surface
}
getRenderableIntersections :: Renderable -> Ray -> [Vector]
getRenderableIntersections re ra = intersections (surface re) ra

Related

Creating list of values of the same typeclass but different types

I'm new to Haskell and trying to do something which I'm sure is easy but I'm not seeing the right way to do it.
What I want is a list of values of a particular typeclass, but different types of that typeclass. Eg:
class Shape a where
area :: a -> Double
numVertices :: a -> Integer
data Triangle = Triangle {...}
data Square = Square {...}
instance Shape Triangle where ...
instance Shape Square where ...
x = [Triangle (...), Square (...)]
I'm getting a compiler error because the list has different types. What's the right way to do what I'm trying to do here? The only thing I've been able to come up with is doing something like this:
data WrappedShape = WrappedShape {
getArea :: () -> Double
, getNumVertices :: () -> Integer
}
wrap s = WrappedShape {
getArea = \ () -> area s
, getNumVertices = \ () -> vertices s
}
x = [wrap (Triangle (...)), wrap (Square (...))]
This works, but it's heavy on boilerplate, since I have to effectively define Shape twice and with differently-named members. What's the standard way to do this sort of thing?
If you just need a few different shapes, you can enumerate each shape as a constructor, here is a example:
data SomeShapes = Triangle {...}
| Square {...}
instance Shape SomeShapes where
area (Triangle x) = ...
area (Square x) = ....
now you can put them in a list, because they are same type of SomeShapes
[Triangle {...}, Square {...}]
Your wrapped type is probably the best idea.
It can be improved by noting that, in a lazy language like Haskell, the type () -> T essentially works like the plain T. You probably want to delay computation and write stuff like let f = \ () -> 1+2 which does not perform addition until the function f is called with argument (). However, let f = 1+2 already does not perform addition until f is really needed by some other expression -- this is laziness.
So, we can simply use
data WrappedShape = WrappedShape {
getArea :: Double
, getNumVertices :: Integer
}
wrap s = WrappedShape {
getArea = area s
, getNumVertices = vertices s
}
x = [wrap (Triangle (...)), wrap (Square (...))]
and forget about passing () later on: when we will access a list element, the area/vertices will be computed (whatever we need). That is print (getArea (head x)) will compute the area of the triangle.
The \ () -> ... trick is indeed needed in eager languages, but in Haskell it is an anti-pattern. Roughly, in Haskell everything has a \ () -> ... on top, roughly speaking, s o there's no need to add another one.
These is another solution to your problem, which is called an "existential type". However, this sometimes turns into an anti-pattern as well, so I do not recommend to use it lightly.
It would work as follows
data WrappedShape = forall a. Shape a => WrappedShape a
x = [WrappedShape (Triangle ...), WrappedShape (Square ...)]
exampleUsage = case head x of WrappedShape s -> area s
This is more convenient when the type class has a lots of methods, since we do not have to write a lot of fields in the wrapped type.
The main downside of this technique is that it involves more complex type machinery, for no real gain. I mean a basic list [(Double, Integer)] has the same functionality of [WrappedShape] (list of existentials), so why bother with the latter?
Luke Palmer wrote about this anti-pattern. I do not agree with that post completely, but I think he does have some good points.
I do not have a clear-cut line where I would start using existentials over the basic approach, but these factors are what I would consider:
How many methods does the type class have?
Are there any methods of the type class where the type a (the one related to the class) appears not only as an argument? E.g. a method foo :: a -> (String, a)?

Enforce class constraints in type class that is not captured in the type signature of implementing type

I am trying to use a typeclass that enforces a constraint on the type returned by one of the functions it defines. But the return type of the function does not capture the constraint in its type variable. I would like to know what is wrong with the code or what is the correct way to encode it.
A sample code is given below:
data State a = State {
uniform :: a
}
class Renderable a where
render :: (Uniform b) => Int -> a -> State b
library :: (Uniform a) => a -> IO ()
-- some implementation
draw :: (Renderable a) => a -> IO ()
draw renderable = do
let state = render 0 renderable
_ <- library (uniform state)
In the above snippet, the render function tries to enforce that the uniform property in State adheres to a class constraint Uniform. When I run the code, I am getting an error that
Could not deduce (Uniform a5) arising from a use of ‘draw’
from the context: (Renderable r, Uniform a)
bound by the type signature for:
draw :: forall r a.
(Renderable r, Uniform a) =>
Int -> Renderable r -> IO ()
Thinking of it, I am sort of able to understand that since the type of draw uses only Renderable and Renderable does not have a parameter of type Uniform in its type signature, the compiler is not able to verify the flow completely. But I am wondering, why cant the compiler, while testing the type signature of draw ignore the issue and basically depend on the fact that it will know if a type implementing Renderable will definitely have to provide a value for uniform as a part of State and it can verify the type correctness in the implementation site rather than usage.
PS: This is an extracted snippet from OpenGL code and Uniform, Library are opengl terminologies.
Here is a technique for you. I've written about this many years ago (in a slightly different context, but the idea is the same) and I still stand by it.
First, the framing. If we write out the signature of render explicitly, we have:
render :: forall b. Uniform b => Int -> a -> State b
That is, the caller of render chooses the type b. It seems to me that your intention is more like this pseudo-Haskell*:
render :: exists b. (Uniform b) & Int -> a -> State b
In which the callee gets to choose the type. That is, different implementations of render may choose different types b to return, so long as they are uniform.
This might be a fine way to phrase it, except that Haskell does not support existential quantification directly. You can make a wrapper data type to simulate it
data SomeUniform where
SomeUniform :: Uniform a => a -> SomeUniform
making your signature
render :: Int -> a -> SomeUniform
which I think has the properties you are looking for. However the SomeUniform type and the Uniform typeclass are very likely superfluous. You said in the comments that the Uniform typeclass looks like this:
class Uniform a where
library :: a -> IO ()
Let's consider this question: let's say we have a SomeUniform, that is, we have a value of some type a about which we know nothing except that it is an instance of the Uniform typeclass. What can we possibly do with x? There is only one way to get any information out of x, and that is to call library on it. So in essence the only thing the SomeUniform type is doing is carrying around a library method to be called later. This whole existential/typeclass is kind of pointless, we would be better served collapsing it down to a simple data type:
data Uniform = Uniform { library :: IO () }
and your render method becomes:
render :: Int -> a -> Uniform
It's so beautifully unfancy, isn't it? If there were more methods in Uniform typeclass, they would become additional fields of this data type (whose types may be functions, which can take some getting used to). Where you had types and instances of the typeclass, e.g.
data Thingy = Thingy String
-- note the constructor type Thingy :: String -> Thingy
instance Uniform String where
library (Thingy s) = putStrLn $ "thingy " ++ s
you can now also be rid of the data type and just use a function in place of the constructor
thingy :: String -> Uniform
thingy s = Uniform { library = putStrLn $ "thingy " ++ s }
(If you can't get rid of the data type for other reasons, you can provide a conversion function instead uniformThingy :: Thingy -> Uniform)
The principle here is, you may replace an existential type with the collection of its observations, and it's usually pretty nice if you do.
* My pseudo-Haskell & is dual to =>, playing essentially the same role but for existentially quantified dictionaries. c => t means that once the caller provides the dictionary c, the type t is returned, whereas c & t means that the callee provides both the dictionary c and the type t.
It appears that you're expecting to be able to define render to return a different distinct type for each implementation of Renderable, as long as that type is Uniform:
instance Renderable Foo where
render _ _ = State True
instance Renderable Bar where
render _ _ = State "mothman"
instance Renderable Baz where
render _ _ = State 19
So if render is called with a Foo, it will return a State Bool, but if it's called with a Bar it will return a State String (assuming both Bool and String are Uniform). This is not how it works, and you'll get a type mismatch error if you try instantiating like this.
render :: (Uniform b) => Int -> a -> State b means that a Uniform b => State b is returned. If this is what your type signature is, your implementation must be no more or less specific; your implementation must be able to return a value of ANY type Uniform b => State b. If it is not able to do so, any code that requests a return value of a specific type won't get the right type, and things will break in ways that the type system SHOULD be able to prevent.
Let's look at a different example:
class Collection t where
size :: Num i => t a -> i
Assume someone wants to run this size function, and get the result as a Double. They can do that, because any implementation of size must be able to return any type of class Num, so the caller can always specify which type they want. If you were allowed to write an implementation that always returned an Integer, this would no longer be possible.
I think to do what you're trying to do, you'd need something like FunctionalDependencies. With this, your class can be something like:
class Uniform b => Renderable a b | a -> b where
render :: Int -> a -> State b
The "| a -> b" tells the type checker that the type b should be decided based on the type a provided by the caller. This disallows the caller from choosing their own b, which means the implementation should force a more specific type. Note that now you need to specify both a and b in your instances, so:
instance Renderable Foo Bool where ...
instance Renderable Bar String where ...
I'm certain there are other valid approaches to this problem, as well.

Iterating over custom data types in Haskell

I have a custom data type that looks like this:
data Circle = Circle
{ radius :: Float
, xPosition :: Float
, yPosition :: Float
}
I want to be able to write a scale function that can take a given circle and change its size like this:
aCircle = Circle 1.5 1 1
scaleFn aCircle 10
The desired output for this example with scale of 10 would be:
Circle 15 10 10
How can I create a function where I can iterate over each field and multiple the values by a constant? In my actual use case I need a way to map over all the fields as there are many of them.
Scaling by a factor is generally a vector space operation. You could do the following:
{-# LANGUAGE TypeFamilies, DeriveGeneric #-}
import Data.VectorSpace
import GHC.Generics (Generic)
data Circle = Circle
{ radius :: Float
, xPosition :: Float
, yPosition :: Float
} deriving (Generic, Show)
instance AdditiveGroup Circle
instance VectorSpace Circle where
type Scalar Circle = Float
main = print $ Circle 1.5 1 1 ^* 10
(result: Circle {radius = 15.0, xPosition = 10.0, yPosition = 10.0}).
(requires vector-space >= 0.11, which has just added support for generic-derived instances.)
However I should remark that Circle as such is not really a good VectorSpace instance: adding two circles doesn't make any sense, and scaling by a negative factor gives a bogus radius. Only define such an instance if your real use case follows the actual vector space axioms.
What you really want for a type like Circle is something like diagrams' Transformable class. But I don't think there's any automatic way to derive an instance for that. In fact, since diagrams has – unfortunately IMO – switched from vector-space to linear, something like this has become considerably tougher to do even in principle.
You can use "scrap your boilerplate":
import Data.Generics
data Circle = Circle
{ radius :: Float
, xPosition :: Float
, yPosition :: Float
}
deriving (Show, Data)
circleModify :: (Float -> Float) -> Circle -> Circle
circleModify f = gmapT (mkT f)
Intuitively, above, mkT f transforms f into a function which is applicable to any type: if the argument of mkT f is a Float, then f is applied, otherwise the argument is returned as it is.
The newly constructed general function is called a "transformation": the T in mkT stands for that.
Then, gmapT applies the transformation mkT f to all the fields of the circle. Note that is a field contained, say, (Float, Bool) that float would be unaffected. Use everywhere instead of gmapT to recursively go deeper.
Note that I'm not a big fan of this approach. If for any reason you change the type of a field, that change will not trigger a type error but gmapT (mkT ...) will now simply skip over that field.
Generic programming can be convenient, but sometimes a bit too much, in that type errors can be silently transformed into unexpected results at runtime. Use with care.

Using subclass implementation in the definition of superclass functions

In my Haskell program I have some typeclasses representing abstract notions of "shapes", namely
-- | Class representing shapes.
class Shape a where
isColliding :: (Shape b) => a -> b -> Bool
centroid :: Point
-- | Class representing shapes composed of a finite number of vertices
and line segments connecting them.
class (Shape a) => Polygon a where
vertices :: a -> Vertices
As you can see, Polygon is naturally a subclass of Shape. I also have some data types that are instances of these different typeclasses. For example:
data Box = Box Point Point Angle
instance Shape Box where
...
instance Polygon Box where
...
---------------------------------
data Circle = Circle Point Radius
instance Shape Circle where
...
I have many more possible shapes, such as NGon, RegularNGon, etc. I would like to be able to implement isColliding, but the information required to calculate whether two shapes are colliding is dependent upon the implementation of the specific instance of Shape. For example, to calculate if two boxes are colliding, I need their list of vertices. So I have a few questions:
Is there anyway to "specialize" my function isColliding so that it is defined in a specific way for collisions of the type isColliding :: (Polygon b) => Box -> b -> Bool?
Is the structuring of my datatypes the best way to approach this problem, or am I misusing typeclasses and datatypes when the whole thing could be restructured to eliminate this problem?
I am rather new to Haskell, so if my question is worded poorly or any clarification is needed, please tell me.
Your current Shape class says “isColliding can tell whether this shape intersects another shape using only the methods of Shape on the other shape”, because its signature (Shape b) => a -> b -> Bool only tells you that b has an instance of Shape. So you’re right that this isn’t quite what you want.
One thing you can do is use MultiParamTypeClasses to describe a relationship between two types:
{-# LANGUAGE MultiParamTypeClasses #-}
class Colliding a b where
collidesWith :: a -> b -> Bool
And then make instances for various concrete combinations of types:
instance Colliding Circle Box where
Circle p r `collidesWith` Box p1 p2 θ = {- … -}
Here you know the concrete types of both a and b when defining the implementation. That might be good enough for your use case.
However, this leaves you with n2 instances if you have n types. And you’ll run into problems if you try to define polymorphic instances like this:
instance (HasBoundingBox b) => Colliding Circle b where
collidesWith = {- … -}
Because this overlaps with all your other instances for Colliding Circle: b will match any type, and only add the constraint that b must have an instance of HasBoundingBox. That constraint is checked after instance resolution. You can work around this with OverlappingInstances or the newer OVERLAPPABLE/OVERLAPPING/OVERLAPS pragmas to tell GHC to choose the most specific matching instance, but this might be more trouble than it’s worth if you’re just getting familiar with Haskell.
I’d have to think on it more, but there are definitely alternative approaches. In the simplest case, if you only need to deal with a few different kinds of shape, then you can just make them a single sum type instead of separate data types:
data Shape
= Circle Point Radius
| Box Point Point Angle
| …
Then your isColliding function can be of type Shape -> Shape -> Bool and just pattern-match on this type.
Generally speaking, if you’re writing a typeclass, it should come with laws for how instances should behave, like mappend x mempty == mappend mempty x == x from Data.Monoid. If you can’t think of any equations that should always hold for instances of your class, you should prefer to represent things with plain old functions and data types instead.

Data member of some class

Simplified problem
Given
class Foo f where
frobnicate :: f -> Float
how could I allow any instance of Foo in
data Bar = Bar { <here> }
?
Actual problem
Given
-- Typically lightweight geometric objects, e.g. spheres
class Shape s where
intersect :: (RealFrac t, Floating t, Ord t, Shape s)
=> Ray t -> s t -> Maybe (DifferentialGeometry t)
and
-- Primitives contain higher level informations, like material properties
class Primitive p where
intersect :: (RealFrac t, Floating t, Ord t, Primitive p)
=> Ray t -> p t -> Maybe (Intersection t)
Note the only difference in the signatures of Primitive.intersect and Shape.intersect lies in the return type.
Now I would like to add a wrapper which basically transforms any Shape into a Primitive.
I would think it works roughly like this:
data ShapeWrapperPrimitive t = ShapeWrapperPrimitive {
shape :: (Shape s) => s t
}
or in other words, I would like to add an arbitrary shape member, which is of the Shape class.
However, this gives me Illegal polymorphic or qualified type.
I'm not sure if your simplified problem is really a simplification of the actual problem. The answer to the simplified problem is:
If the only thing you can do with an unknown type that is an instance of class Foo is to turn it into a Float, then you can just as well store the Float.
So you'd use
data Bar = Bar Float
However, if I understand your actual problem correctly, then you want to wrap a type that is an instance of class Shape and thereby turn it into an instance of class Primitive. For this, I'd define
newtype ShapeWrapperPrimitive s t = ShapeWrapperPrimitive (s t)
and then say
instance Shape s => Primitive (ShapeWrapperPrimitive s) where
intersect = ... -- fill in definition here
This isn't an answer to the question you asked, but it may be helpful. If you're creating a list with both Shapes and Primitives, then you need a wrapper type, as described by thoferon. But if you're not, then maybe you don't really need a wrapper type.
You said "Note the only difference in the signatures of Primitive.intersect and Shape.intersect lies in the return type." You can represent that relationship using type families, as shown below. This gives you a type family called Thing. The result type of intersect can be different for each type that is an instance of Thing.
{-# LANGUAGE TypeFamilies, TypeSynonymInstances #-}
class Thing t where
type Result t
intersect :: Ray t -> s t -> Maybe (Result t)
-- Made-up type definitions just to get things to compile
data Shape s t = Shape s t
data Primitive p t = Primitive p t
type Ray t = (Double, t)
type DifferentialGeometry t = [t]
type Intersection t = [t]
-- Typically lightweight geometric objects, e.g. spheres
instance Thing (Shape s t) where
type Result (Shape s t) = DifferentialGeometry t
intersect a b = undefined
-- Primitives contain higher level informations, like material properties
instance Thing (Primitive p t) where
type Result (Primitive p t) = Intersection t
intersect a b = undefined
I can see two solutions to this kind of problems :
1) Use the language extension ExistentialQuantification. So you can write :
data Blah = forall a. Num a => Blah a
2) Move the constraint to your functions, like
data Blah a = Blah a
f :: (Num a) => Blah a -> a
f = undefined
or your instances :
instance (Num a) => Foo (Blah a) where
-- ...
Even though I accepted another answer, I'll post this for future visitors.
My problem was more or less a what could be considered a typo. At some point, I had
23: data ShapeWrapperPrimitive s t = ShapeWrapperPrimitive s t
24:
25: instance (Shape s) => Primitive (ShapeWrapperPrimitive s) where
26: intersect _ _ = Nothing
--- >> line 25: Expecting one more argument to `s'
which let me to a path of confusion and torment. Notice how it points me to line 25. The accepted answer uncovered my mistake: Instead of
data ShapeWrapperPrimitive s t = ShapeWrapperPrimitive s t
I was in need of
data ShapeWrapperPrimitive s t = ShapeWrapperPrimitive (s t)
The first would have added an s and a t as a members, whereas I really wanted an s t; adding the parens solved my problem.

Resources