I'm trying to work out how to implement the concepts of associated types and constants for a typeclass in Haskell.
As practice, I am trying to make a typeclass for A* nodes. A node has the given traits:
Eq
, Data.Hashable
)neighbours
, provides a list of neighbouring nodes (i.e. neighbours :: Node -> [Node]
)Num
and Ord
. It cannot simply be hardcoded to use float
or something of that nature, as the concept of "distance" could have different precision requirements or even use something like manhattan distance on a 2D integer grid.For those also familiar with rust as I am, the equivalent trait to what I am trying to define as a typeclass would be:
trait NavNode : Eq + Hash + Sized {
type Distance: Ord + Add;
const INFINITY: Self::Distance;
const ZERO: Self::Distance;
fn heuristic(a: Self, b: Self) -> Self::Distance;
fn neighbors(self) -> Vec<Self>;
}
The nearest to an implementation I've managed to make is this, but I've found no way to constrain the associated Distance
type to be Num
and Ord
, and the compiler does not like my definitions for the zero
and infinity
constants or usage of Distance a
, which it confusingly seems to insist ought to be some Distance a0
.
{-# LANGUAGE TypeFamilies #-}
class (Eq a, Hashable a) => NavNode a where
type Distance a :: * -- How to tell it it's Num, Ord?
heuristic :: a -> a -> Distance a
neighbours :: a -> [a]
zero :: Distance a
infinity :: Distance a
This is an example of code that compiles. I have removed Hashable
for simplicity, but you can add it back in your real code.
{-# LANGUAGE TypeFamilies, AllowAmbiguousTypes #-}
import Data.Kind
class (Eq a, Ord (Distance a), Num (Distance a)) => NavNode a where
type Distance a :: Type -- The line above requires this to be Ord and Num
heuristic :: a -> a -> Distance a
neighbours :: a -> [a]
zero :: Distance a
infinity :: Distance a
-- Dummy instance: it's nonsense, but it shows the main ideas.
instance NavNode String where
type Distance String = Int
heuristic x y = abs (length x - length y)
neighbours x = [x]
zero = 0
infinity = 1000
main :: IO ()
main = print (infinity @String)
Note the @String
in the last line, which is mandatory so to specify the actual instance. Indeed, multiple types can have Int
as their associated distance type, so we have to specify it to disambiguate.