misplaces SPECIALISE
Simon Peyton-Jones
simonpj@microsoft.com
Wed, 24 Apr 2002 04:28:23 -0700
The SPECIALIZE instance pragma must be in the instance decl
itself:
instance (TrieKey key, Binary elem) =3D> Binary (Trie key elem) where
put_ h (Trie e arr) =3D put_ h e >> put_ h (assocs arr)
get h =3D get h >>=3D \e -> get h >>=3D \a -> return (Trie e =
(listArray
(0,255) a))
{-# SPECIALIZE instance Binary (Trie Token Double) #-}
The documentation is wrong in the current web page, but it's
right in the HEAD so it'll percolate to the web in due course.
Simon
| -----Original Message-----
| From: Hal Daume III [mailto:hdaume@ISI.EDU]
| Sent: 23 April 2002 15:43
| To: Simon Peyton-Jones
| Cc: GHC Users Mailing List
| Subject: RE: misplaces SPECIALISE
|=20
|=20
| Here is sufficient code, using ghc5.02.1 for solaris:
|=20
| module Test where
|=20
| import Util.Binary -- this is the GHC binary distribution import=20
| PrelWord import Array
|=20
| newtype Token =3D Token [Word8]
|=20
| class TrieKey key where
| mkKey :: key -> [Word8]
| unKey :: [Word8] -> key
|=20
| data Trie key elem =3D Trie !(Maybe elem) (Array Word8 (Maybe (Trie =
key
| elem)))
|=20
| instance (TrieKey key, Binary elem) =3D> Binary (Trie key elem) where
| put_ h (Trie e arr) =3D put_ h e >> put_ h (assocs arr)
| get h =3D get h >>=3D \e -> get h >>=3D \a -> return (Trie e =
(listArray
| (0,255) a))
| {-# SPECIALIZE instance Binary (Trie Token Double) #-}
|=20
|=20
| wherever I put the specialize pragma, it complains:
|=20
| /nfs/isd/hdaume/projects/Test.hs:18:
| Misplaced SPECIALISE instance pragma:
| {-# SPECIALIZE instance {Binary (Trie Token Double)} #-}
|=20
| I also tried something like (I don't have the 100% correct code but=20
| something like):
|=20
| putTDT :: BinHandle -> Trie Token Double -> IO ()
| putTDT h (Trie e arr) =3D put_ h e' >> put_ h (assocs arr)
| where e' =3D case e of {Nothing->0; Just x->x}
| and a corresponding "getTDT" then:
|=20
| {-# SPECIALIZE put_ :: BinHandle -> Trie Token Double -> IO
| () =3D putTDT #-}
|=20
| and the corresponding for get, but it complained with a parse error on
| "=3D"
|=20
| - Hal
|=20
| --
| Hal Daume III
|=20
| "Computer science is no more about computers | hdaume@isi.edu
| than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume
|=20
| On Mon, 22 Apr 2002, Simon Peyton-Jones wrote:
|=20
| > It is really hard to help you if you don't supply the
| context. Which
| > version of GHC? Send the code for Trie.lhs. etc.
| >=20
| > Otherwise we're all guessing.
| >=20
| > Simon
| >=20
| > | -----Original Message-----
| > | From: Hal Daume III [mailto:hdaume@ISI.EDU]
| > | Sent: 22 April 2002 23:46
| > | To: GHC Users Mailing List
| > | Subject: misplaces SPECIALISE
| > |=20
| > |=20
| > | /nfs/isd/hdaume/projects/NLP/Trie.lhs:162:
| > | Misplaced SPECIALISE instance pragma:
| > | {-# SPECIALIZE instance {Binary (Trie Token Double)} #-}
| > | Failed, modules loaded: NLP.NLPPrelude, Util.BinUtil, Util.Binary,
| > | NLP.HashMap, Util.ShrinkString, Util.FastMutInt, NLP.Util.
| > |=20
| > |=20
| > | what does that mean?
| > |=20
| > | --
| > | Hal Daume III
| > |=20
| > | "Computer science is no more about computers | hdaume@isi.edu
| > | than astronomy is about telescopes." -Dijkstra |=20
| > | www.isi.edu/~hdaume
| > |=20
| > | _______________________________________________
| > | Glasgow-haskell-users mailing list
| > | Glasgow-haskell-users@haskell.org=20
| > | http://www.haskell.org/mailman/listinfo/glasgow-| haskell-users
| > |=20
| >=20
|=20
|=20