Describing a typeclass for general graphs in Haskell - haskell

I'm trying to write a typeclass for graphs. Basically, the typeclass looks like:
class Graph g where
adjacentNodes :: g n -> n -> [n]
in which I use n to represent the type of nodes.
Then I have the following Graph defined like this:
data FiniteGraph n = FiniteGraph { runFiniteGraph :: Array n [n] }
where Array is adopted from the standard container Data.Array, the structure is to represent a finite graph in the way to map each node to their adjacent nodes.
Here comes the problem, when I try to make FiniteGraph an instance of Graph.
instance Graph FiniteGraph where
adjacentNodes g n = (runFiniteGraph g) ! n
Unfortunately this doesn't work, because the ! operator requires the constraint Ix n, but I find no where to declare it.
I expect the instance declaration to be some like:
instance (Ix n) => Graph (FiniteGraph n) where { ... }
But this requires the g in class Graph g to have the kind * instead of * -> *, such that I would have no where to show that n depend on g.
So what can I do with that? Thanks.

It can be done after you add a second param to the Graph class.
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
import Data.Array
class Graph g n | n -> g where
adjacentNodes :: g n -> n -> [n]
data FiniteGraph n = FiniteGraph { runFiniteGraph :: Array n [n] }
instance Ix n => Graph FiniteGraph n where
adjacentNodes g n = (runFiniteGraph g) ! n
That makes sense if you think about it: graph requires the notion of a vertex.

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.

Impose nesting limits on recursive data structure

Consider a recursive data structure like the following:
data Tree level
= Leaf String
| Node level [ Tree level ]
Now, if level is an instance of Ord, I would like to impose at the type level the following limitation on the data structure: a node must contain only Trees with a higher level.
You can safely assume that level is a simple sum type like
Level
= Level1
| Level2
...
| LevelN
but where N is not known a priori. In this case I would be able to have that all the subnodes of a node have a higher level.
For example
tree = Node Level1
[ Node Level2 []
, Node Level3 []
]
should compile, while
tree = Node Level2
[ Node Level1 []
]
should not.
Is it possible to model such a thing in Haskell?
Here's the basic idea. The easiest way to encode recursion limits like this is to use Peano numbers. Let's define such a type.
data Number = Zero | Succ Number
A number is either zero or the successor of another number. This is a nice way to define numbers here, as it will get along nicely with our tree recursion. Now, we want the Level to be a type, not a value. If it's a value, we can't limit its value at the type level. So we use GADTs to restrict the way we can initialize things.
data Tree (lvl :: Number) where
Leaf :: String -> Tree lvl
Node :: [Tree lvl] -> Tree ('Succ lvl)
lvl is the depth. A Leaf node can have any depth, but a Node node is restricted in its depth and must be strictly greater than that of its children (here, strictly one greater, which works in most simple cases. Allowing it to be strictly greater in general would require some more complicated type-level tricks, possibly with -XTypeInType). Notice that we use 'Succ at the type level. This is a promoted type, enabled with -XDataKinds. We also need -XKindSignatures to enable the :: Number constraint.
Now let's write a function.
f :: Tree ('Succ 'Zero) -> String
f _ = "It works!"
This function only takes trees that go at most one level deep. We can try to call it.
f (Leaf "A") -- It works!
f (Node [Leaf "A"]) -- It works!
f (Node [Node [Leaf "A"]]) -- Type error
So it will fail at compile-time if the depth is too much.
Complete example (including compiler extensions):
{-# LANGUAGE GADTs, KindSignatures, DataKinds #-}
data Number = Zero | Succ Number
data Tree (lvl :: Number) where
Leaf :: String -> Tree lvl
Node :: [Tree lvl] -> Tree ('Succ lvl)
f :: Tree ('Succ 'Zero) -> String
f _ = "It works!"
This isn't everything you can do with this. There's certainly expansions to be made, but it gets the point across and will hopefully point you in the right direction.
So there are a number of difficulties with this question. Peano numbers are a good place to start, though:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ConstraintKinds #-}
data Nat = Z | S Nat
Next, we'll need some way of saying one number is "bigger" than another. We can do so by first defining an inductive class for "n is less than or equal to m"
class (n :: Nat) <= (m :: Nat)
instance Z <= n
instance n <= m => (S n <= S m)
We can then define "less than" in terms of this:
type n < m = S n <= m
Finally, here's the Tree and Levels:
data Tree n where
Leaf :: String -> Tree n
Node :: n < z => Level z -> [Tree z] -> Tree n
data Level n where
Level0 :: Level Z
Level1 :: Level (S Z)
Level2 :: Level (S (S Z))
Level3 :: Level (S (S (S Z)))
Level4 :: Level (S (S (S (S Z))))
And, as desired, the first example compiles:
tree = Node Level1
[ Node Level2 []
, Node Level3 []
]
While the second does not:
tree = Node Level2
[ Node Level1 []
]
Just for extra fun, we can now add a "custom type error" (this will need UndecidableInstances:
import GHC.TypeLits (TypeError, ErrorMessage(Text))
instance TypeError (Text "Nodes must contain trees of a higher level") => S n < Z
So when you write:
tree = Node Level2
[ Node Level1 []
]
You get the following:
• Nodes must contain trees of a higher level
• In the expression: Node Level1 []
In the second argument of ‘Node’, namely ‘[Node Level1 []]’
In the expression: Node Level2 [Node Level1 []]
If you want to make "level" more generic, you'll need a couple more extensions:
{-# LANGUAGE TypeApplications, RankNTypes, AllowAmbiguousTypes, TypeFamilies #-}
import qualified GHC.TypeLits as Lits
data Level n where
Level0 :: Level Z
LevelS :: !(Level n) -> Level (S n)
class HasLevel n where level :: Level n
instance HasLevel Z where level = Level0
instance HasLevel n => HasLevel (S n) where level = LevelS level
type family ToPeano (n :: Lits.Nat) :: Nat where
ToPeano 0 = Z
ToPeano n = S (ToPeano (n Lits.- 1))
node :: forall q z n m. (ToPeano q ~ z, HasLevel z, n < z) => [Tree z] -> Tree n
node = Node level
tree =
node #1
[ node #2 []
, node #3 []
]

Haskell: Non type-variable argument in the constraint

I created some functions to get some comfort with 2D geometry.
In this example I use Geom2D from CubicBezier package.
Complete code of my program: https://gist.github.com/nskeip/3784d651ac646a67c5f246f048949af4
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-}
import Geom2D
left :: (Num a) => Point a -> a -> Point a
left (Point x y) n = Point (x - n) y
right :: (Num a) => Point a -> a -> Point a
right (Point x y) n = Point (x + n) y
up :: (Num a) => Point a -> a -> Point a
up (Point x y) n = Point x (y - n)
down :: (Num a) => Point a -> a -> Point a
down (Point x y) n = Point x (y + n)
They work like this:
> (Point 0 0) `up` 10
Point 0.0 -10.0
Where Point is defined like this:
data Point a = Point {
pointX :: !a,
pointY :: !a
} deriving (Eq, Ord, Functor, Foldable, Traversable)
And everything was fine untill I thought: "Hey, it would be nice to make that functions (actualy, operators) work with thigs like Line - not only Point"
So I declared a class (not taking left and right to keep thigs simple):
class Num n => Moving p n where
up' :: n -> p -> p
down' :: n -> p -> p
up' n = down' (-n)
down' n = up' (-n)
And an instance of Moving for Point a data type:
instance Num a => Moving (Point a) a where
up' n (Point x y) = Point x (y - n)
But when I try to use it, I got an error:
✗ ghci ./uno.hs
GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help
[1 of 1] Compiling Main ( uno.hs, interpreted )
Ok, modules loaded: Main.
*Main> let p = Point { pointX = 0, pointY = 0 }
*Main> up' 10 p
<interactive>:3:1:
Non type-variable argument in the constraint: Moving (Point a) n
(Use FlexibleContexts to permit this)
When checking that ‘it’ has the inferred type
it :: forall n a. (Num a, Moving (Point a) n) => Point a
And the thing that confuses me much: I put the FlexibleContexts pragma to the pragma listing in the head, but ghcu still suggest me to get it included.
How can I fix my class / instance to get parametric polymorphism working? :)
And the thing that confuses me much: I put the FlexibleContexts pragma to the pragma listing in the head, but ghcu still suggest me to get it included.
This only enables the extension in the module itself. To write this code in GHCi, you need to enable the extension in GHCi: :set -XFlexibleContexts.
But this is only part of the problem. It looks like for your class p should determine n: you can only move a Point a up and down by a, right? But as it stands, nothing stops you from defining more Moving (Point a) SomeOtherType instances, and the compiler doesn't assume you won't. So a and n in the inferred type are completely unrelated, where you want them to be the same. This can be fixed by adding the FunctionalDependencies extension and changing the class declaration to say
class Num n => Moving p n | p -> n where
which means exactly that there can't be instances with same p and different n.
I think that's enough to make it work. The code will still be underdetermined because it allows any numeric a, but defaulting rules will pick Integer.

Haskell instance signatures

I'm a complete newbie in Haskell so please be patient.
Let's say I've got this class
class Indexable i where
at :: i a p -> p -> a
Now let's say I want to implement that typeclass for this data type:
data Test a p = Test [a]
What I tried is:
instance Indexable Test where
at (Test l) p = l `genericIndex` p
However it didn't compile, because p needs to be an Integral, however as far as I understand, it's impossibile to add the type signature to instances. I tried to use InstanceSigs, but failed.
Any ideas?
here is a version where you add the index-type to the class using MultiParamTypeClasses
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
module Index where
import Data.List (genericIndex)
class Indexable i f where
at :: forall a . f a -> i -> a
data Test a = Test [a]
instance Integral i => Indexable i Test where
at (Test as) i = as `genericIndex` i
here I need the FlexibleInstances because of the way the instance is declared and RankNTypes for the forall a . ;)
assuming this is your expected behavior:
λ> let test = Test [1..5]
λ> test `at` 3
4
λ> test `at` 0
1
λ> test `at` (0 :: Int)
1
λ> test `at` (1 :: Integer)
2
Just for fun, here's a very different solution which doesn't require any changes to your class declaration. (N.B. This answer is for fun only! I do not advocate keeping your class as-is; it seems a strange class definition to me.) The idea here is to push the burden of proof off from the class instance to the person constructing a value of type Test p a; we will demand that constructing such a value will require an Integral p instance in scope.
All this code stays exactly the same (but with a new extension turned on):
{-# LANGUAGE GADTs #-}
import Data.List
class Indexable i where
at :: i a p -> p -> a
instance Indexable Test where
at (Test l) p = l `genericIndex` p
But the declaration of your data type changes just slightly to demand an Integral p instance:
data Test a p where
Test :: Integral p => [a] -> Test a p
You are actually trying to do something fairly advanced. If I understand what you want, you actually need a multiparameter typeclass here, because your type parameter "p" depends on "i": for a list indexed by integer you need "p" to be integral, but for a table indexed by strings you need it to be "String", or at least an instance of "Ord".
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-} -- Enable the language extensions.
class Indexable i p | i -> p where
at :: i a -> p -> a
This says that the class is for two types, "i" and "p", and if you know "i" then "p" follows automatically. So if "i" is a list the "p" has to be Int, and if "i" is a "Map String a" then "p" has to be "String".
instance Indexable [a] Int where
at = (!!)
This declares the combination of [a] and Int as being an instance of Indexable.
user2407038 has provided an alternative approach using "type families", which is a more recent and sophisticated version of multiparameter type classes.
You can use associated type families and constraint kinds:
import GHC.Exts(Constraint)
class Indexable i where
type IndexableCtr i :: * -> Constraint
at :: IndexableCtr i p => i a p -> p -> a
instance Indexable Test where
type IndexableCtr Test = Integral
at (Test l) p = l `genericIndex` p
This defines the class Indexable with an associated type IndexableCtr which
is used to constraint the type of at.

OCaml functors (parametrized modules) emulation in Haskell

Is there any recommended way to use typeclasses to emulate OCaml-like parametrized modules?
For an instance, I need the module that implements the complex
generic computation, that may be parmetrized with different
misc. types, functions, etc. To be more specific, let it be
kMeans implementation that could be parametrized with different
types of values, vector types (list, unboxed vector, vector, tuple, etc),
and distance calculation strategy.
For convenience, to avoid crazy amount of intermediate types, I want to
have this computation polymorphic by DataSet class, that contains all
required interfaces. I also tried to use TypeFamilies to avoid a lot
of typeclass parameters (that cause problems as well):
{-# Language MultiParamTypeClasses
, TypeFamilies
, FlexibleContexts
, FlexibleInstances
, EmptyDataDecls
, FunctionalDependencies
#-}
module Main where
import qualified Data.List as L
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as U
import Distances
-- contains instances for Euclid distance
-- import Distances.Euclid as E
-- contains instances for Kulback-Leibler "distance"
-- import Distances.Kullback as K
class ( Num (Elem c)
, Ord (TLabel c)
, WithDistance (TVect c) (Elem c)
, WithDistance (TBoxType c) (Elem c)
)
=> DataSet c where
type Elem c :: *
type TLabel c :: *
type TVect c :: * -> *
data TDistType c :: *
data TObservation c :: *
data TBoxType c :: * -> *
observations :: c -> [TObservation c]
measurements :: TObservation c -> [Elem c]
label :: TObservation c -> TLabel c
distance :: TBoxType c (Elem c) -> TBoxType c (Elem c) -> Elem c
distance = distance_
instance DataSet () where
type Elem () = Float
type TLabel () = Int
data TObservation () = TObservationUnit [Float]
data TDistType ()
type TVect () = V.Vector
data TBoxType () v = VectorBox (V.Vector v)
observations () = replicate 10 (TObservationUnit [0,0,0,0])
measurements (TObservationUnit xs) = xs
label (TObservationUnit _) = 111
kMeans :: ( Floating (Elem c)
, DataSet c
) => c
-> [TObservation c]
kMeans s = undefined -- here the implementation
where
labels = map label (observations s)
www = L.map (V.fromList.measurements) (observations s)
zzz = L.zipWith distance_ www www
wtf1 = L.foldl wtf2 0 (observations s)
wtf2 acc xs = acc + L.sum (measurements xs)
qq = V.fromList [1,2,3 :: Float]
l = distance (VectorBox qq) (VectorBox qq)
instance Floating a => WithDistance (TBoxType ()) a where
distance_ xs ys = undefined
instance Floating a => WithDistance V.Vector a where
distance_ xs ys = sqrt $ V.sum (V.zipWith (\x y -> (x+y)**2) xs ys)
This code somehow compiles and work, but it's pretty ugly and hacky.
The kMeans should be parametrized by value type (number, float point number, anything),
box type (vector,list,unboxed vector, tuple may be) and distance calculation strategy.
There are also types for Observation (that's the type of sample provided by user,
there should be a lot of them, measurements that contained in each observation).
So the problems are:
1) If the function does not contains the parametric types in it's signature,
types will not be deduced
2) Still no idea, how to declare typeclass WithDistance to have different instances
for different distance type (Euclid, Kullback, anything else via phantom types).
Right now WithDistance just polymorphic by box type and value type, so if we need
different strategies, we may only put them in different modules and import the required
module. But this is a hack and non-typed approach, right?
All of this may be done pretty easy in OCaml with is't modules. What the proper approach
to implement such things in Haskell?
Typeclasses with TypeFamilies somehow look similar to parametric modules, but they
work different. I really need something like that.
It is really the case that Haskell lacks useful features found in *ML module systems.
There is ongoing effort to extend Haskell's module system: http://plv.mpi-sws.org/backpack/
But I think you can get a bit further without those ML modules.
Your design follows God class anti-pattern and that is why it is anti-modular.
Type class can be useful only if every type can have no more than a single instance of that class. E.g. DataSet () instance fixes type TVect () = V.Vector and you can't easily create similar instance but with TVect = U.Vector.
You need to start with implementing kMeans function, then generalize it by replacing concrete types with type variables and constraining those type variables with type classes when needed.
Here is little example. At first you have some non-general implementation:
kMeans :: Int -> [(Double,Double)] -> [[(Double,Double)]]
kMeans k points = ...
Then you generalize it by distance calculation strategy:
kMeans
:: Int
-> ((Double,Double) -> (Double,Double) -> Double)
-> [(Double,Double)]
-> [[(Double,Double)]]
kMeans k distance points = ...
Now you can generalize it by type of points, but this requires introducing a class that will capture some properties of points that are used by distance computation e.g. getting list of coordinates:
kMeans
:: Point p
=> Int -> (p -> p -> Coord p) -> [p]
-> [[p]]
kMeans k distance points = ...
class Num (Coord p) => Point p where
type Coord p
coords :: p -> [Coord p]
euclidianDistance
:: (Point p, Floating (Coord p))
=> p -> p -> Coord p
euclidianDistance a b
= sum $ map (**2) $ zipWith (-) (coords a) (coords b)
Now you may wish to make it a bit faster by replacing lists with vectors:
kMeans
:: (Point p, DataSet vec p)
=> Int -> (p -> p -> Coord p) -> vec p
-> [vec p]
kMeans k distance points = ...
class DataSet vec p where
map :: ...
foldl' :: ...
instance Unbox p => DataSet U.Vector p where
map = U.map
foldl' = U.foldl'
And so on.
Suggested approach is to generalize various parts of algorithm and constrain those parts with small loosely coupled type classes (when required).
It is a bad style to collect everything in a single monolithic type class.

Resources