2009-06-19 88 views
7

我要定義以下類型類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 

一個Mapping實例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 

現在我想創建一個類型Trie :: * -> * -> * -> *

{-# 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) 

到目前爲止好, 現在我也想定義Trieinsertempty,這就是我遇到問題的地方。

我將討論empty,因爲它更簡單和insert需要它無論如何.. 如果我試試這個:

instance Mapping k (Trie m k v) m => Mapping [k] v (Trie m k) where 
    empty = Trie { trValue = Nothing, trChildren = empty } 
    ... 

,這讓我得到以下錯誤:

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} 

我已經嘗試並試圖解決它但失敗。

有誰知道如何使它工作?它甚至有可能嗎?

+3

順便說一句,我建議從類型定義中除去`v`(但將其留在方法的簽名中)。你不需要它,至少對於你迄今爲止給出的所有結構,因爲它們都將採取任何包含的類型,並且它使得一切都變得更簡單。 – 2009-06-19 21:42:53

回答

14

添加functional dependency

{-# LANGUAGE ..., FunctionalDependencies #-} 

class Mapping k v m | m -> k where 
    ... 

你得到之前是因爲該方案是含糊不清的哪個鍵式在某些地方使用,因此錯誤有關類型變量​​的錯誤。函數依賴允許從映射類型推導出鍵類型(通過聲明只有一個可能的答案),它處理這個問題。

+0

謝謝!我對它進行了編碼(見下文),並且由於你有關從類型定義中刪除v的建議,它非常整潔。 – yairchu 2009-06-19 22:22:08

7

代碼來演示Ganesh的答案:

{-# 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) 

順便說一句:假如函數依賴不存在,我們可能需要妥協的一個惱人的接口上,並使用功能表,而不是類型類。

+0

@Titou:關於你的編輯 - 參見上面關於@GaneshSittampalam的關於從類型定義中去除`v`的討論。 http://stackoverflow.com/questions/1019928/haskell-type-classes-question/1020264#comment829685_1019928 http://stackoverflow.com/questions/1019928/haskell-type-classes-question/1020264#comment829844_1020134 – yairchu 2014-07-02 21:51:05