You don't need to create a new type for a String -> Int hashtable, you already get it for free because HashTable is a parameterized type.

Also, although you are apparently trying to make life simpler for yourself using a HashTable, you are actually making like more complicated because the Data.HashTable implementation can only be worked with inside the IO monad.  So what you'd need is something like:


====================

import Prelude hiding (lookup)
import Data.HashTable

dummy s = 7

main = do
ht <- new (==) dummy
insert ht "Foo" 12
        value <- lookup ht "Foo"
        putStrLn . show $ value

====================

Note that I didn't have to label any of the types;  Haskell is smart enough to mostly infer all of them automatically.  The main reason to include types is if there is some ambiguity.  So for example, if you actually wanted to map Strings to Floats, then you would need to explicitly tell it somewhere that the values it is storing are floats.  You could do this by either pinning down explicitly the HashTable type:

====================

import Prelude hiding (lookup)
import Data.HashTable

dummy s = 7

main = do
ht <- new (==) dummy  :: IO (HashTable String Float)
insert ht "Foo" 12
        value <- lookup ht "Foo"
        putStrLn . show $ value

====================

Or just by pinning down the type of a value that you insert into it:

====================

import Prelude hiding (lookup)
import Data.HashTable

dummy s = 7

main = do
ht <- new (==) dummy
insert ht "Foo" (12 :: Float)
        value <- lookup ht "Foo"
        putStrLn . show $ value

====================

Again, the downside though is that you can't work with HashTable outside of the IO monad.  If what you want is just a map from strings to values, then you probably are better off using Data.Map:

====================

import Prelude hiding (lookup)
import Data.Map

my_map = empty :: Map String Int

my_map_after_adding_key = insert "Foo" 12 my_map

value_associated_with_Foo = lookup "Foo" my_map_after_adding_key

main = putStrLn . show $ value_associated_with_Foo

====================

Cheers,
Greg

On Nov 17, 2009, at 11:16 AM, michael rice wrote:

I'm trying to create a hash table. Yeah, I know, don't use hash tables, but I need to create something I'm familiar with, not something I've never worked with before. What's wrong with this code?

Michael

====================

import Prelude hiding (lookup)
import Data.HashTable

data MyHashTable = HashTable String Int

dummy:: String -> Int
dummy s = 7

ht = MyHashTable.new (==) dummy

====================

[michael@localhost ~]$ ghci hash1
GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main             ( hash1.hs, interpreted )

hash1.hs:9:5: Not in scope: `MyHashTable.new'
Failed, modules loaded: none.
Prelude>


_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe