Reputation: 24814
I wish to define the following typeclass Mapping
:
{-# LANGUAGE MultiParamTypeClasses #-}
class Mapping k v m where
empty :: m v
insert :: k -> v -> m v -> m v
search :: k -> m v -> Maybe v
delete :: k -> m v -> m v
One instance of Mapping
is Data.Map.Map
{-# LANGUAGE ..., FlexibleInstances #-}
instance Ord k => Mapping k v (Map.Map k) where
empty = Map.empty
search = Map.lookup
insert = Map.insert
delete = Map.delete
And now I want to create a type Trie :: * -> * -> * -> *
such as
{-# LANGUAGE ..., UndecidableInstances #-}
data Trie m k v = Trie {
trValue :: Maybe v,
trChildren :: m (Trie m k v)
}
instance Mapping k (Trie m k v) m => Mapping [k] v (Trie m k) where
search [] tree = trValue tree
search (x:xs) tree =
search xs =<< search x (trChildren tree)
So far so good,
now I also want to define Trie
's insert
and empty
, and that's where I get into problems.
I will discuss empty
because it's simpler and insert
needs it anyhow..
If I try this:
instance Mapping k (Trie m k v) m => Mapping [k] v (Trie m k) where
empty = Trie { trValue = Nothing, trChildren = empty }
...
and that makes me get the following error:
Could not deduce (Mapping k (Trie m k1 v) (m k1))
from the context (Mapping [k1] v (Trie m k1),
Mapping k1 (Trie m k1 v) (m k1))
arising from a use of `empty' at test.hs:27:49-53
Possible fix:
add (Mapping k (Trie m k1 v) (m k1)) to the context of
the instance declaration
or add an instance declaration for (Mapping k (Trie m k1 v) (m k1))
In the `trChildren' field of a record
In the expression: Trie {trValue = Nothing, trChildren = empty}
In the definition of `empty':
empty = Trie {trValue = Nothing, trChildren = empty}
I've tried and tried to solve it but failed.
Does anyone know how to make it work? Is it even possible?
Upvotes: 7
Views: 1065
Reputation: 24814
Code to demonstrate Ganesh's answer:
{-# LANGUAGE FlexibleInstances, FunctionalDependencies, MultiParamTypeClasses, StandaloneDeriving, UndecidableInstances #-}
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
class Mapping k m | m -> k where
empty :: m v
insert :: k -> v -> m v -> m v
search :: k -> m v -> Maybe v
delete :: k -> m v -> m v
instance Ord k => Mapping k (Map.Map k) where
empty = Map.empty
search = Map.lookup
insert = Map.insert
delete = Map.delete
data Trie m v = Trie {
trValue :: Maybe v,
trChildren :: m (Trie m v)
}
deriving instance (Show v, Show (m (Trie m v))) => Show (Trie m v)
trieMod :: Mapping k m => Maybe v -> [k] -> Trie m v -> Trie m v
trieMod val [] trie = trie { trValue = val }
trieMod val (x:xs) trie =
trie { trChildren = insert x newChild children }
where
children = trChildren trie
newChild = trieMod val xs prevChild
prevChild = fromMaybe empty . search x $ children
instance Mapping k m => Mapping [k] (Trie m) where
empty = Trie { trValue = Nothing, trChildren = empty }
search [] trie = trValue trie
search (x:xs) trie =
search xs =<< search x (trChildren trie)
insert key val = trieMod (Just val) key
delete = trieMod Nothing
type TernarySearchTree a = Trie (Map.Map a)
Btw: Had functional dependencies not existed, we would probably need to compromise on an annoying interface and use function tables instead of type classes.
Upvotes: 7
Reputation: 29110
Add a functional dependency:
{-# LANGUAGE ..., FunctionalDependencies #-}
class Mapping k v m | m -> k where
...
The errors you got before were because the program was ambiguous about which key type to use in certain places, hence the errors about the type variable k1
. The functional dependency allows the key type to be deduced from the map type (by declaring that there is only one possible answer), which deals with this problem.
Upvotes: 14