
I want to use the list-tries package for a little hobby project, but my naive idea about how it should work is obviously wrong: module TryPat where import Data.ListTrie.Patricia.Map a = singleton "harry" 99 yields the error: No instance for (Data.ListTrie.Base.Map.Map map0 Char) arising from a use of `singleton' Possible fix: add an instance declaration for (Data.ListTrie.Base.Map.Map map0 Char) In the expression: singleton "harry" 99 In an equation for `a': a = singleton "harry" 99 Now, there is some stuff about this in the docs: The data types are parametrized over the map type they use internally to store the child nodes: this allows extending them to support different kinds of key types or increasing efficiency. Child maps are required to be instances of the Map class in Data.ListTrie.Base.Maphttp://hackage.haskell.org/packages/archive/list-tries/0.4.1/doc/html/Data-L.... Some operations additionally require an OrdMap instance. But frankly, I don't understand it, especially the type signatures. Any hints on how I might go about making an instance for Map map0 Char?

Hi Matthew You'll have to give `a` a concrete type, as `singleton` is overloaded, GHC cannot infer a type. The TrieMap type is quite complicated as it allows different representations of (finite) Maps within it. There are three different internal maps you can use (the three pre-defined instances of the Map class - Data.Map, WrappedIntMap and AList) - I'd go for Data.Map as it will be faster than AList and I think you are using Char for key so you can't use an IntMap. I don't have the package `list-tries` installed but I'd guess at one of these two for the concrete type signature. Assuming you have imported Data.Map as import qualified Data.Map as Map (Probably this...) a :: TrieMap Map.Map [Char] Int (Possibly this...) a :: TrieMap (Map.Map Char Int) [Char] Int

Thanks a lot, Stephen - was just about giving up on this.
The correct type signature turned out to be:
import Data.ListTrie.Patricia.Map as P
import qualified Data.Map as Map
a :: P.TrieMap Map.Map Char Int
a = P.singleton "harry" 99
On Tue, Dec 20, 2011 at 1:07 AM, Stephen Tetley
Hi Matthew
You'll have to give `a` a concrete type, as `singleton` is overloaded, GHC cannot infer a type.
The TrieMap type is quite complicated as it allows different representations of (finite) Maps within it. There are three different internal maps you can use (the three pre-defined instances of the Map class - Data.Map, WrappedIntMap and AList) - I'd go for Data.Map as it will be faster than AList and I think you are using Char for key so you can't use an IntMap.
I don't have the package `list-tries` installed but I'd guess at one of these two for the concrete type signature.
Assuming you have imported Data.Map as
import qualified Data.Map as Map
(Probably this...) a :: TrieMap Map.Map [Char] Int
(Possibly this...) a :: TrieMap (Map.Map Char Int) [Char] Int
participants (2)
-
Matthew Moppett
-
Stephen Tetley