[Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread bbrown
I am using the Data.Binary module and having some issues reading big endian
files (actually, just reading the file).  I can read the header but not the
rest of the data which contains a set of row information.  Also, go ahead and
make fun my style of coding.

Anyway, This is the my code and the error at the bottom.


The issue stems from here, it says I didn't define an instance, but I did:

instance Binary URLSet where
put _ = do BinaryPut.putWord8 0
get = do
  remainingByteData - BinaryGet.getRemainingLazyByteString
  i :: URLInfo - decode remainingByteData
  j :: TitleInfo - decode remainingByteData
  k :: DescrInfo - decode remainingByteData
  x :: KeywordsInfo - decode remainingByteData
  return (URLSet {urlinfo=i, titleinfo=j, 
  descrinfo=k, keywordsinfo=x})

-

module Main where

import Data.Word
import Data.Binary
import qualified Data.ByteString.Lazy.Char8 as BSLC8
import Data.ByteString.Lazy (ByteString)
import Data.Binary.Get as BinaryGet
import Data.Binary.Put as BinaryPut
import IO
import Text.Printf
import System.Environment
import Control.Monad (replicateM, liftM)

{- *
 Define the Database Data Types
 SpiderDatabase represents a singleton wrapper for an
 entire database.
   * -}
data SpiderDatabase =  SpiderDatabase { 
  magicNumberA :: Word16,
  magicNumberB :: Word16,
  majorVers :: Word16,
  minorVers :: Word16,
  headerTag :: Word16,
  poolLen :: Word16,
  spiderpool :: [URLSet]
}
data URLSet = URLSet {
  urlinfo :: URLInfo,
  titleinfo :: TitleInfo,
  descrinfo :: DescrInfo,
  keywordsinfo :: KeywordsInfo
}
data URLInfo = URLInfo {
  tag :: Word8,
  urlid :: Word16,
  urllen :: Word16,
  url :: ByteString
}
data TitleInfo = TitleInfo {
  titletag :: Word8,  
  titlelen :: Word16,
  title :: ByteString
}
data DescrInfo = DescrInfo {
  descrtag :: Word8,  
  descrlen :: Word16,
  descr :: ByteString
}
data KeywordsInfo = KeywordsInfo {
  keywordstag :: Word8,  
  keywordslen :: Word16,
  keywords :: ByteString
}
{- *
 Class instances
   * -}
instance Show SpiderDatabase where
show db = let magicb = (magicNumberB db)
  header = (headerTag db)
  poolct = (poolLen db)
  in Database Content\n ++
 (((printf Magic: %X %X\n) (magicNumberA db)) (magicNumberB
db)) ++
 printf URL Pool Count: %d\n poolct ++
 End

instance Binary URLInfo where
put _ = do BinaryPut.putWord8 0
get = do
  urltag - getWord8
  idx - getWord16be
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (URLInfo {tag=urltag, urlid=idx, 
   urllen=len, url=strdata})
instance Binary DescrInfo where
put _ = do BinaryPut.putWord8 0
get = do
  tag - getWord8
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (DescrInfo {descrtag=tag,
 descrlen=len, 
 descr=strdata})
instance Binary TitleInfo where
put _ = do BinaryPut.putWord8 0
get = do
  tag - getWord8
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (TitleInfo {titletag=tag,
 titlelen=len, 
 title=strdata})
instance Binary KeywordsInfo where
put _ = do BinaryPut.putWord8 0
get = do
  tag - getWord8
  len - getWord16be
  strdata - BinaryGet.getLazyByteString (fromIntegral len)
  return (KeywordsInfo {keywordstag=tag,
keywordslen=len, 
keywords=strdata})
instance Binary URLSet where
put _ = do BinaryPut.putWord8 0
get = do
  remainingByteData - BinaryGet.getRemainingLazyByteString
  i :: URLInfo - decode remainingByteData
  j :: TitleInfo - decode remainingByteData
  k :: DescrInfo - decode remainingByteData
  x :: KeywordsInfo - decode remainingByteData
  return (URLSet {urlinfo=i, titleinfo=j, 
  descrinfo=k, keywordsinfo=x})
  
instance Binary SpiderDatabase where
put _ = do BinaryPut.putWord8 0
get = do 
  magicnumbera - BinaryGet.getWord16be
  magicnumberb - BinaryGet.getWord16be
  major - BinaryGet.getWord16be
  minor - BinaryGet.getWord16be
  header - BinaryGet.getWord16be
  poolct - BinaryGet.getWord16be
  -- ***
  -- Get the remaining byte string data,
  -- So that we can use lazy bytestring to load to load the
  -- the data types.
  -- ***

Re: [Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread Daniel Fischer
I've no experience with Data.Binary, but I noticed you declared

instance Binary YourType where...

and the compiler says

instance Binary (Get YourType)

is missing. That might be worth looking into.
Cheers,
Daniel

Am Freitag, 4. Januar 2008 00:13 schrieb bbrown:
 I am using the Data.Binary module and having some issues reading big endian
 files (actually, just reading the file).  I can read the header but not the
 rest of the data which contains a set of row information.  Also, go ahead
 and make fun my style of coding.

 Anyway, This is the my code and the error at the bottom.


 The issue stems from here, it says I didn't define an instance, but I did:

 instance Binary URLSet where
 put _ = do BinaryPut.putWord8 0
 get = do
   remainingByteData - BinaryGet.getRemainingLazyByteString
   i :: URLInfo - decode remainingByteData
   j :: TitleInfo - decode remainingByteData
   k :: DescrInfo - decode remainingByteData
   x :: KeywordsInfo - decode remainingByteData
   return (URLSet {urlinfo=i, titleinfo=j,
   descrinfo=k, keywordsinfo=x})

 -

 module Main where

 import Data.Word
 import Data.Binary
 import qualified Data.ByteString.Lazy.Char8 as BSLC8
 import Data.ByteString.Lazy (ByteString)
 import Data.Binary.Get as BinaryGet
 import Data.Binary.Put as BinaryPut
 import IO
 import Text.Printf
 import System.Environment
 import Control.Monad (replicateM, liftM)

 {- *
  Define the Database Data Types
  SpiderDatabase represents a singleton wrapper for an
  entire database.
* -}
 data SpiderDatabase =  SpiderDatabase {
   magicNumberA :: Word16,
   magicNumberB :: Word16,
   majorVers :: Word16,
   minorVers :: Word16,
   headerTag :: Word16,
   poolLen :: Word16,
   spiderpool :: [URLSet]
 }
 data URLSet = URLSet {
   urlinfo :: URLInfo,
   titleinfo :: TitleInfo,
   descrinfo :: DescrInfo,
   keywordsinfo :: KeywordsInfo
 }
 data URLInfo = URLInfo {
   tag :: Word8,
   urlid :: Word16,
   urllen :: Word16,
   url :: ByteString
 }
 data TitleInfo = TitleInfo {
   titletag :: Word8,
   titlelen :: Word16,
   title :: ByteString
 }
 data DescrInfo = DescrInfo {
   descrtag :: Word8,
   descrlen :: Word16,
   descr :: ByteString
 }
 data KeywordsInfo = KeywordsInfo {
   keywordstag :: Word8,
   keywordslen :: Word16,
   keywords :: ByteString
 }
 {- *
  Class instances
* -}
 instance Show SpiderDatabase where
 show db = let magicb = (magicNumberB db)
   header = (headerTag db)
   poolct = (poolLen db)
   in Database Content\n ++
  (((printf Magic: %X %X\n) (magicNumberA db))
 (magicNumberB db)) ++
  printf URL Pool Count: %d\n poolct ++
  End

 instance Binary URLInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   urltag - getWord8
   idx - getWord16be
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (URLInfo {tag=urltag, urlid=idx,
urllen=len, url=strdata})
 instance Binary DescrInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   tag - getWord8
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (DescrInfo {descrtag=tag,
  descrlen=len,
  descr=strdata})
 instance Binary TitleInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   tag - getWord8
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (TitleInfo {titletag=tag,
  titlelen=len,
  title=strdata})
 instance Binary KeywordsInfo where
 put _ = do BinaryPut.putWord8 0
 get = do
   tag - getWord8
   len - getWord16be
   strdata - BinaryGet.getLazyByteString (fromIntegral len)
   return (KeywordsInfo {keywordstag=tag,
 keywordslen=len,
 keywords=strdata})
 instance Binary URLSet where
 put _ = do BinaryPut.putWord8 0
 get = do
   remainingByteData - BinaryGet.getRemainingLazyByteString
   i :: URLInfo - decode remainingByteData
   j :: TitleInfo - decode remainingByteData
   k :: DescrInfo - decode remainingByteData
   x :: KeywordsInfo - decode remainingByteData
   return (URLSet {urlinfo=i, titleinfo=j,
   descrinfo=k, keywordsinfo=x})

 instance Binary SpiderDatabase where
 put _ = do BinaryPut.putWord8 0
 get = do
   magicnumbera - BinaryGet.getWord16be
   magicnumberb - 

Re: [Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread Brandon S. Allbery KF8NH


On Jan 3, 2008, at 18:13 , bbrown wrote:


DbReader.hs:119:22:
No instance for (Binary (Get URLInfo))
  arising from a use of `decode' at DbReader.hs:119:22-45


Without looking more closely, this suggests to me that you have  
mismatched or incorrectly encapsulated monads (for example, treating  
a value in the Get monad as if it were pure).  This might be related  
to the way you specify the types of the values obtained from decode.


(I haven't used Data.Binary.)

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Instance classes and error (also, related to Data.Binary.GET)

2008-01-03 Thread Clive Brettingham-Moore

Like the previous no experience with Data.Binary, but my (rusty) monad
experience is enough to see the source of the problem:
bbrown wrote:

The issue stems from here, it says I didn't define an instance, but I did:

instance Binary URLSet where
put _ = do BinaryPut.putWord8 0
get = do
  remainingByteData - BinaryGet.getRemainingLazyByteString
  i :: URLInfo - decode remainingByteData
  j :: TitleInfo - decode remainingByteData
  k :: DescrInfo - decode remainingByteData
  x :: KeywordsInfo - decode remainingByteData
  return (URLSet {urlinfo=i, titleinfo=j, 
  descrinfo=k, keywordsinfo=x})


  

Data.Binary seems to use the Get monad which looks to be a garden
variety parsing monad.

For  line in the do block:

 i :: URLInfo - decode remainingByteData


Because of the way do notation works x::a - is expecting a value of M a
for a monad M, above Get URLInfo, inplying a type of ByteString - (Get
URLInfo) for decode and therefore the comiler is looking for the
corresponding Binary instance (and of course, not finding it since,
quite properly, your binary instance is URLInfo not Get URLInfo). If you
can't follow this, find a monad tutorial and look at how do notation
expands to = and .

The code you have almost certainly isn't doing what you want/expect
(even if you fix the bad monad nesting you are trying to repeatedly
decode the same data as different types). Not knowing exactly how your
data is encoded it is hard to be certain of the correct code but
something like this seems more likely (untried):

instance Binary URLSet where
   put _ = do BinaryPut.putWord8 0
   get = do
 i :: URLInfo - get
 j :: TitleInfo - get
 k :: DescrInfo - get
 x :: KeywordsInfo - get
 return (URLSet {urlinfo=i, titleinfo=j,
 descrinfo=k, keywordsinfo=x})

This assumes that the data contains the structures serialized in order.
In this case for i the type of get is inferred to Get URLInfo - which
will work since URLInfo has a Binary instance.

You also have a similar issue in the SpiderDatabase instance.

Clive





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