Typeclass instances with constrained return type - haskell

I'm implementing a notion of inner product that's general over the container and numerical types. The definition states that the return type of this operation is a (non-negative) real number.
One option (shown below) is to write all instances by hand, for each numerical type (Float, Double, Complex Float, Complex Double, Complex CFloat, Complex CDouble, etc.). The primitive types aren't many, but I dislike the repetition.
Another option, or so I thought, is to have a parametric instance with a constraint such as RealFloat (which represents Float and Double).
{-# language MultiParamTypeClasses, TypeFamilies, FlexibleInstances #-}
module Test where
import Data.Complex
class Hilbert c e where
type HT e :: *
dot :: c e -> c e -> HT e
instance Hilbert [] Double where
type HT Double = Double
dot x y = sum $ zipWith (*) x y
instance Hilbert [] (Complex Double) where
type HT (Complex Double) = Double
a `dot` b = realPart $ sum $ zipWith (*) (conjugate <$> a) b
Question
Why does the instance below not work ("Couldn't match type e with Double.. expected type HT e, actual type e")?
instance RealFloat e => Hilbert [] e where
type HT e = Double
dot x y = sum $ zipWith (*) x y

Well, that particular instance doesn't work because the sum only yields an e, but you want the result to be Double. As e is constrained to RealFrac, this is easy to fix though, as any Real (questionable though is is mathematically) can be converted to a Fractional:
dot x y = realToFrac . sum $ zipWith (*) x y
However, that generic instance prevents you from also defining complex instances: with instance RealFloat e => Hilbert [] e where you cover all types, even if they aren't really real numbers. You could still instantiate Complex as an overlapping instance, but I'd rather stay away from those if I could help it.
It's also questionable if such vectorspace classes should be defined on * -> * at all. Yes, linear also does it this way, but IMO parametricity doesn't work in our favour in this application. Have you checked out the vector-space package? Mind, it isn't exactly complete for doing serious linear algebra; that's a gap I hope to fill with my linearmap-category package.

Related

Matrix dimensionality checks at compile time

I was wondering whether is was possible to use the matrix type from Data.Matrix to construct another type with which it becomes possible to perform dimensionality checking at compile time.
E.g. I want to be able to write a function like:
mmult :: Matrix' r c -> Matrix' c r -> Matrix' r r
mmult = ...
However, I don't see how to do this since the arguments to a type constructor Matrix' would have to be types and not integer constants.
I don't see how to do this since the arguments to a type constructor Matrix' would have to be types and not integer constants
They do need to be type-level values, but not necessarily types. “Type-level” basically just means known at compile-time, but this also contains stuff that isn't really types. Types are in particular the type-level values of kind Type, but you can also have type-level strings or, indeed, natural numbers.
{-# LANGUAGE DataKinds, KindSignatures #-}
import GHC.TypeLits
import Data.Matrix
newtype Matrix' (n :: Nat) (m :: Nat) a
= StaMat {getStaticSizeMatrix :: Matrix a}
mmult :: Num a => Matrix' n m a -> Matrix' l n a -> Matrix' l m a
mmult (StaMat f) (StaMat g) = StaMat $ multStd f g
I would remark that matrices are only a special case of a much more general mathematical concept, that of linear maps between vector spaces. And since vector spaces can be seen as particular types, it actually makes a lot of sense to not use mere integers as the type-level tags, but the actual spaces. What you have then is a category, and it allows you to deal with both dynamic- and static size matrix/vector types, and can even be generalised to completely different spaces like infinite-dimensional Hilbert spaces.
{-# LANGUAGE GADTs #-}
newtype StaVect (n :: Nat) a
= StaVect {getStaticSizeVect :: Vector a}
data LinMap v w where
StaMat :: Matrix a -> LinMap (StaVec n a) (StaVec m a)
-- ...Add more constructors for mappings between other sorts of vector spaces...
linCompo :: LinMap v w -> LinMap u v -> LinMap u w
linCompo (StaMat f) (StaMat g) = StaMat $ multStd f g
The linearmap-category package pursues this direction.

What can type families do that multi param type classes and functional dependencies cannot

I have played around with TypeFamilies, FunctionalDependencies, and MultiParamTypeClasses. And it seems to me as though TypeFamilies doesn't add any concrete functionality over the other two. (But not vice versa). But I know type families are pretty well liked so I feel like I am missing something:
"open" relation between types, such as a conversion function, which does not seem possible with TypeFamilies. Done with MultiParamTypeClasses:
class Convert a b where
convert :: a -> b
instance Convert Foo Bar where
convert = foo2Bar
instance Convert Foo Baz where
convert = foo2Baz
instance Convert Bar Baz where
convert = bar2Baz
Surjective relation between types, such as a sort of type safe pseudo-duck typing mechanism, that would normally be done with a standard type family. Done with MultiParamTypeClasses and FunctionalDependencies:
class HasLength a b | a -> b where
getLength :: a -> b
instance HasLength [a] Int where
getLength = length
instance HasLength (Set a) Int where
getLength = S.size
instance HasLength Event DateDiff where
getLength = dateDiff (start event) (end event)
Bijective relation between types, such as for an unboxed container, which could be done through TypeFamilies with a data family, although then you have to declare a new data type for every contained type, such as with a newtype. Either that or with an injective type family, which I think is not available prior to GHC 8. Done with MultiParamTypeClasses and FunctionalDependencies:
class Unboxed a b | a -> b, b -> a where
toList :: a -> [b]
fromList :: [b] -> a
instance Unboxed FooVector Foo where
toList = fooVector2List
fromList = list2FooVector
instance Unboxed BarVector Bar where
toList = barVector2List
fromList = list2BarVector
And lastly a surjective relations between two types and a third type, such as python2 or java style division function, which can be done with TypeFamilies by also using MultiParamTypeClasses. Done with MultiParamTypeClasses and FunctionalDependencies:
class Divide a b c | a b -> c where
divide :: a -> b -> c
instance Divide Int Int Int where
divide = div
instance Divide Int Double Double where
divide = (/) . fromIntegral
instance Divide Double Int Double where
divide = (. fromIntegral) . (/)
instance Divide Double Double Double where
divide = (/)
One other thing I should also add is that it seems like FunctionalDependencies and MultiParamTypeClasses are also quite a bit more concise (for the examples above anyway) as you only have to write the type once, and you don't have to come up with a dummy type name which you then have to type for every instance like you do with TypeFamilies:
instance FooBar LongTypeName LongerTypeName where
FooBarResult LongTypeName LongerTypeName = LongestTypeName
fooBar = someFunction
vs:
instance FooBar LongTypeName LongerTypeName LongestTypeName where
fooBar = someFunction
So unless I am convinced otherwise it really seems like I should just not bother with TypeFamilies and use solely FunctionalDependencies and MultiParamTypeClasses. Because as far as I can tell it will make my code more concise, more consistent (one less extension to care about), and will also give me more flexibility such as with open type relationships or bijective relations (potentially the latter is solver by GHC 8).
Here's an example of where TypeFamilies really shines compared to MultiParamClasses with FunctionalDependencies. In fact, I challenge you to come up with an equivalent MultiParamClasses solution, even one that uses FlexibleInstances, OverlappingInstance, etc.
Consider the problem of type level substitution (I ran across a specific variant of this in Quipper in QData.hs). Essentially what you want to do is recursively substitute one type for another. For example, I want to be able to
substitute Int for Bool in Either [Int] String and get Either [Bool] String,
substitute [Int] for Bool in Either [Int] String and get Either Bool String,
substitute [Int] for [Bool] in Either [Int] String and get Either [Bool] String.
All in all, I want the usual notion of type level substitution. With a closed type family, I can do this for any types (albeit I need an extra line for each higher-kinded type constructor - I stopped at * -> * -> * -> * -> *).
{-# LANGUAGE TypeFamilies #-}
-- Subsitute type `x` for type `y` in type `a`
type family Substitute x y a where
Substitute x y x = y
Substitute x y (k a b c d) = k (Substitute x y a) (Substitute x y b) (Substitute x y c) (Substitute x y d)
Substitute x y (k a b c) = k (Substitute x y a) (Substitute x y b) (Substitute x y c)
Substitute x y (k a b) = k (Substitute x y a) (Substitute x y b)
Substitute x y (k a) = k (Substitute x y a)
Substitute x y a = a
And trying at ghci I get the desired output:
> :t undefined :: Substitute Int Bool (Either [Int] String)
undefined :: Either [Bool] [Char]
> :t undefined :: Substitute [Int] Bool (Either [Int] String)
undefined :: Either Bool [Char]
> :t undefined :: Substitute [Int] [Bool] (Either [Int] String)
undefined :: Either [Bool] [Char]
With that said, maybe you should be asking yourself why am I using MultiParamClasses and not TypeFamilies. Of the examples you gave above, all except Convert translate to type families (albeit you will need an extra line per instance for the type declaration).
Then again, for Convert, I am not convinced it is a good idea to define such a thing. The natural extension to Convert would be instances such as
instance (Convert a b, Convert b c) => Convert a c where
convert = convert . convert
instance Convert a a where
convert = id
which are as unresolvable for GHC as they are elegant to write...
To be clear, I am not saying there are no uses of MultiParamClasses, just that when possible you should be using TypeFamilies - they let you think about type-level functions instead of just relations.
This old HaskellWiki page does an OK job of comparing the two.
EDIT
Some more contrasting and history I stumbled upon from augustss blog
Type families grew out of the need to have type classes with
associated types. The latter is not strictly necessary since it can be
emulated with multi-parameter type classes, but it gives a much nicer
notation in many cases. The same is true for type families; they can
also be emulated by multi-parameter type classes. But MPTC gives a
very logic programming style of doing type computation; whereas type
families (which are just type functions that can pattern match on the
arguments) is like functional programming.
Using closed type families
adds some extra strength that cannot be achieved by type classes. To
get the same power from type classes we would need to add closed type
classes. Which would be quite useful; this is what instance chains
gives you.
Functional dependencies only affect the process of constraint solving, while type families introduced the notion of non-syntactic type equality, represented in GHC's intermediate form by coercions. This means type families interact better with GADTs. See this question for the canonical example of how functional dependencies fail here.

Haskell type signature with composite/multi-param type constructors

I've discovered these kinds of type signatures:
x :: a b -> Int
x f = 3
y :: a b c -> Int
y f = 3
z :: a b c d -> Int
z f = 3
> x [1] -- 3
> y (1, 2) -- 3
> z (1, 2, 3) -- 3
Basically:
x only accepts a value inhabiting a type constructor with 1 parameter or more.
y only accepts a value inhabiting a type constructor with 2 parameters or more.
z only accepts a value inhabiting a type constructor with 3 parameters or more.
They are valid, but I'm not sure what they mean nor what they could be used for.
They seem related to polytypic notions or polymorphism over type constructors, but enforce an invariant based on many parameters the type constructor accepts.
Without further constraints, such types are useless – there's nothing you could really do with them, expect pass them right on. But that's actually the same situation with a signature a -> Int: if nothing is known about a, there's nothing you can do with it either!
However, like with e.g. toInteger :: Integral a => a -> Integer, adding constraints to the arguments allows you to do stuff. For instance,
import Data.Foldable
import Prelude hiding (foldr)
x' :: (Foldable a, Integral b) => a b -> Integer
x' = foldr ((+) . toInteger) 0
Rather more often than not, when you have a type of the form a b ... n o p q, then a b ... p is at least an instance of the Functor class, often also Applicative and Monad; sometimes Foldable, Traversable, or Comonad; sometimes a b ... o will be Arrow... These constraints allow you to do quite a lot with the composite types, without knowing what particular type constructors you're dealing with.
After studying #leftaroundabout answer and experimenting in GHCI, I've come to an understanding with composite types. Their unification with applied types is based on both the evaluation order and their type variable's kind signature. The evaluation order is quite important as a b c ~ (((a) b) c) while a (b c) is (a ((b) c). This makes a b c match composite types where a is matched with type constructors of kind * -> * -> *, and a b with * -> * and a b c with *.
I explained it fully with diagrams and GHCI code in this gist (https://gist.github.com/CMCDragonkai/2a1d3ecb67dcdabfc7e0) (it's too long for stack overflow)

Multi-parameter typeclass instance declarations

I am trying to understand multiparameter typeclasses but I just don't get the instance declarations. I am starting out trying to make an InnerProductSpace typeclass for a Vector type so that I can perform a dot product on two vectors. To start out I just wanted to see if I could multiply the first element of each vector. Here is my code
class InnerProductSpace a b c where
dot :: a -> b -> c
data Vector = Vector [Double]
deriving (Show)
instance InnerProductSpace Vector Vector Double where
dot (Vector a) (Vector b) = (head a * head b)
and the error after trying to use the dot function is
No instance for (InnerProductSpace Vector Vector c0)
arising from a use of `dot'
The type variable `c0' is ambiguous
Possible fix: add a type signature that fixes these type variable(s)
Note: there is a potential instance available:
instance InnerProductSpace Vector Vector Double
-- Defined at Vector.hs:8:10
Possible fix:
add an instance declaration for
(InnerProductSpace Vector Vector c0)
In the expression: dot a b
In an equation for `it': it = dot a b
What did I do wrong? Thanks!
The problem is that the compiler doesn't know how to choose the right instance given what it knows. If you try something like
vectorA `dot` vectorA
the compiler goes searching for the right dot knowing that its type must be dot :: Vector -> Vector -> c0. Unfortunately, that's just not enough information by itself—c0 could be anything and the compiler never assumes that just because it only has a single instance it must be the correct one (this is related to the open world assumption---there might be another instance out there the compiler hasn't seen yet, so it prefers to just throw an error). You could get away with it by explicitly telling the compiler what the result ought to be
vectorA `dot` vectorB :: Double
but this is tedious and likely to fail a lot with numeric types since so often those types are generic as well. For instance, which instance of Num is used here?
(vectorA `dot` vectorB) + 3
We know it's Double, but the compiler can't prove that.
One solution is to use Type Families as #AndrewC suggests in the comment. I actually highly recommend that. The other solution you'll see in the wild is Functional Dependencies. These are written like this
class InnerProductSpace a b c | a b -> c where
dot :: a -> b -> c
and translate to entail a promise to the compiler: "knowing a and b is enough information to uniquely identify c". The compiler keeps you honest as well as it'll prevent you from writing instances that conflict on that promise.
instance InnerProductSpace Vector Vector Double where
dot (Vector a) (Vector b) = (head a * head b)
instance InnerProductSpace Vector Vector Float where
dot (Vector a) (Vector b) = (head a * head b)
---
/Users/tel/tmp/foo.hs:10:10:
Functional dependencies conflict between instance declarations:
instance InnerProductSpace Vector Vector Double
-- Defined at /Users/tel/tmp/foo.hs:10:10
instance InnerProductSpace Vector Vector Float
-- Defined at /Users/tel/tmp/foo.hs:13:10
But the promise gives the compiler exactly enough information to resolve the Double in the previous example.
Main*> (Vector [1,2,3]) `dot` (Vector [2,3,4]) + 3.0
5
or use TypeFamilies
class (D a b ~ c) => InnerProductSpace a b c where
type D a b
dot :: a -> b -> c
or
class InnerProductSpace a b where
type D a b :: *
dot :: a -> b -> D a b
instance InnerProductSpace Vector Vector where
type D Vector Vector = Double
dot (Vector a) (Vector b) = (head a * head b)

How to have an operator which adds/subtracts both absolute and relative values, in Haskell

(Apologies for the weird title, but I could not think of a better one.)
For a personal Haskell project I want to have the concepts of 'absolute values' (like a frequency) and relative values (like the ratio between two frequencies). In my context, it makes no sense to add two absolute values: one can add relative values to produce new relative values, and add a relative value to an absolute one to produce a new absolute value (and likewise for subtraction).
I've defined type classes for these: see below. However, note that the operators ##+ and #+ have a similar structure (and likewise for ##- and #-). Therefore I would prefer to merge these operators, so that I have a single addition operator, which adds a relative value (and likewise a single subtraction operator, which results in a relative value). UPDATE: To clarify, my goal is to unify my ##+ and #+ into a single operator. My goal is not to unify this with the existing (Num) + operator.
However, I don't see how to do this with type classes.
Question: Can this be done, and if so, how? Or should I not be trying?
The following is what I currently have:
{-# LANGUAGE MultiParamTypeClasses #-}
class Abs a where
nullPoint :: a
class Rel r where
zero :: r
(##+) :: r -> r -> r
neg :: r -> r
(##-) :: Rel r => r -> r -> r
r ##- s = r ##+ neg s
class (Abs a, Rel r) => AbsRel a r where
(#+) :: a -> r -> a
(#-) :: a -> a -> r
I think you're looking for a concept called a Torsor. A torsor consists of set of values, set of differences, and operator which adds a difference to a value. Additionally, the set of differences must form an additive group, so differences also can be added together.
Interestingly, torsors are everywhere. Common examples include
Points and Vectors
Dates and date-differences
Files and diffs
etc.
One possible Haskell definition is:
class Torsor a where
type TorsorOf a :: *
(.-) :: a -> a -> TorsorOf a
(.+) :: a -> TorsorOf a -> a
Here are few example instances:
instance Torsor UTCTime where
type TorsorOf UTCTime = NominalDiffTime
a .- b = diffUTCTime a b
a .+ b = addUTCTime b a
instance Torsor Double where
type TorsorOf Double = Double
a .- b = a - b
a .+ b = a + b
instance Torsor Int where
type TorsorOf Int = Int
a .- b = a - b
a .+ b = a + b
In the last case, notice that the two sets of the torsors don't need to be a different set, which makes adding your relative values together simple.
For more information, see a much nicer description in Roman Cheplyakas blog
I don't think you should be trying to unify these operators. Subtracting two vectors and subtracting two points are fundamentally different operations. The fact that it's difficult to represent them as the same thing in the type system is not the type system being awkward - it's because these two concepts really are different things!
The mathematical framework behind what you're working with is the affine space.
These are already available in Haskell in the vector-space package (do cabal install vector-space at the command prompt). Rather than using multi parameter type classes, they use type families to associate a vector (relative) type with each point (absolute) type.
Here's a minimal example showing how to define your own absolute and relative data types, and their interaction:
{-# LANGUAGE TypeFamilies #-}
import Data.VectorSpace
import Data.AffineSpace
data Point = Point { px :: Float, py :: Float }
data Vec = Vec { vx :: Float, vy :: Float }
instance AdditiveGroup Vec where
zeroV = Vec 0 0
negateV (Vec x y) = Vec (-x) (-y)
Vec x y ^+^ Vec x' y' = Vec (x+x') (y+y')
instance AffineSpace Point where
type Diff Point = Vec
Point x y .-. Point x' y' = Vec (x-x') (y-y')
Point x y .+^ Vec x' y' = Point (x+x') (y+y')
You have two answers telling you what you should do, here's another answer telling you how to do what you asked for (which might not be a good idea). :)
class Add a b c | a b -> c where
(#+) :: a -> b -> c
instance Add AbsTime RelTime AbsTime where
(#+) = ...
instance Add RelTime RelTime RelTime where
(#+) = ...
The overloading for (#+) makes it very flexible. Too flexible, IMO. The only restraint is that the result type is determined by the argument types (without this FD the operator becomes almost unusable because it constrains nothing).

Resources