Data.ByteString.Lazy.ByteString vs Data.ByteString.Lazy.Internal.ByteString

Hi, I noticed that even though I declare the type of a function in my code as Data.ByteString.Lazy.ByteString ... when I check it out in ghci using :t, it shows this - Data.ByteString.Lazy.Internal.ByteString Is this expected? Regards, Kashyap

ckkashyap:
Hi, I noticed that even though I declare the type of a function in my code as� Data.ByteString.Lazy.ByteString ... when I check it out in ghci using :t, it shows this -�Data.ByteString.Lazy.Internal.ByteString Is this expected?
Yep, the 'Internal' module is where the type is defined, and then re-exported through the regular module. All is well. -- Don

Hi Don,
What would be a good way to figure out the usage of ByteString -
particularly the PS constructor.
Regards,
Kashyap
On Fri, Feb 11, 2011 at 10:01 AM, C K Kashyap
Yep, the 'Internal' module is where the type is defined, and then re-exported through the regular module.
Thanks Don ... good to know. Regards, Kashyap

It is a goal of the ByteString library that you should almost never need to work directly with the PS constructor and the things used in that definition. If you find some task involving IO or string manipulation that seems to require using the internal operations, it's probably worth bringing it up on the list. That said, it's always good to know how things work, and the internals may be relevant if you want to make an interface to a foreign library use ByteStrings. Look at the Foreign.* modules to see how to work with Ptr values, especially Foreign.ForeignPtr, Foreign.Ptr, Foreign.Marshal: http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.3.1.0/Foreign-F... http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.3.1.0/Foreign-P... http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.3.1.0/Foreign-M... The GHC manual has a little bit on unboxed types like Int# http://www.haskell.org/ghc/docs/latest/html/users_guide/primitives.html GHC.Prim provides the basic operations http://www.haskell.org/ghc/docs/latest/html/libraries/ghc-prim-0.2.0.0/GHC-P... There is also the original paper (from Simon Peyton-Jones' page) http://research.microsoft.com/en-us/um/people/simonpj/papers/unboxed-values.... Brandon

Thanks Brandon, data Endian = Big | Little data Size = Eight | Sixteen | ThirtyTwo | SixtyFour type EncTuple = (Int,Size,Endian) My requirement is to write encode :: [EncTuple] -> ByteString I'd like to use it with just the libraries that are part of the platform - and I am not a fan of using the internal stuff :) I'd appreciate it very much if you could give me a sample. And thank you very much for http://research.microsoft.com/en-us/um/people/simonpj/papers/unboxed-values.... Regards, Kashyap

On Monday 14 March 2011 05:45:04, C K Kashyap wrote:
Thanks Brandon,
data Endian = Big | Little data Size = Eight | Sixteen | ThirtyTwo | SixtyFour type EncTuple = (Int,Size,Endian)
My requirement is to write encode :: [EncTuple] -> ByteString
Looks like a job for Data.Binary.
I'd like to use it with just the libraries that are part of the platform
I don't know whether binary is in the platform, though (but I expect it to be).
- and I am not a fan of using the internal stuff :) I'd appreciate it very much if you could give me a sample.
instance Binary Endian where put Big = putWord8 0 put Little = putWord8 1 get = do w <- getWord8 case w of 0 -> return Big 1 -> return Little _ -> error ("Bad Endian tag: " ++ show w) instance Binary Size where put Eight = putWord8 8 put Sixteen = putWord8 16 ... get = do w <- getWord8 case w of 8 -> return 8 ... putAux Eight _ i = putWord8 (fromIntegral i) putAux Sixteen Big i = putWord16be (fromIntegral i) ...

Am 14.03.2011 06:26, schrieb C K Kashyap:
Looks like a job for Data.Binary.
> I'd like to use it with just the libraries that are part of the platform
I forgot to mention, Data.Binary does not seem to be in the platform.
Right, it is not in the platform, but I would recommend to install those packages that you find useful (and vote for packages to be included into later versions of the platform.) Interestingly, there is a hidden package ghc-binary-0.5.0.2, which almost looks like binary-0.5.0.2. Maybe ghc developers and platform maintainers could comment on any differences. If there are none you could simple "ghc-pkg expose ghc-binary". For future versions of ghc and the platform a single ghc-binary or binary version would be better. Cheers Christian

On 14/03/2011 10:33, Christian Maeder wrote:
Am 14.03.2011 06:26, schrieb C K Kashyap:
Looks like a job for Data.Binary.
> I'd like to use it with just the libraries that are part of the platform
I forgot to mention, Data.Binary does not seem to be in the platform.
Right, it is not in the platform, but I would recommend to install those packages that you find useful (and vote for packages to be included into later versions of the platform.)
Interestingly, there is a hidden package ghc-binary-0.5.0.2, which almost looks like binary-0.5.0.2.
Maybe ghc developers and platform maintainers could comment on any differences. If there are none you could simple "ghc-pkg expose ghc-binary". For future versions of ghc and the platform a single ghc-binary or binary version would be better.
You shouldn't use ghc-binary. It is indeed the same as binary, and is required because GHC uses it internally, but binary is not a platform package so we renamed it to ghc-binary and set it to be "hidden" by default. Cheers, Simon

I had started exploring the internal - PS constructor route looking at the base64 encoding implementation by Bryan (which is really fast - http://www.serpentine.com/blog/2010/09/02/fast-base64-encoding-and-decoding-... I was wondering if we don't use the PS constructor can we implement base64 encoding that's comparable? I mean, can we create an asymptotically similar implementation? Regards, Kashyap

On Thu, Mar 17, 2011 at 12:51 AM, C K Kashyap
I had started exploring the internal - PS constructor route looking at the base64 encoding implementation by Bryan (which is really fast - http://www.serpentine.com/blog/2010/09/02/fast-base64-encoding-and-decoding-... )- I was wondering if we don't use the PS constructor can we implement base64 encoding that's comparable? I mean, can we create an asymptotically similar implementation? Regards, Kashyap
I'm a fan of Data.ByteString.Unsafe.unsafeUseAsCStringLen when I need access to the raw buffer. http://hackage.haskell.org/packages/archive/bytestring/0.9.1.10/doc/html/Dat... Antoine
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (7)
-
Antoine Latter
-
Brandon Moore
-
C K Kashyap
-
Christian Maeder
-
Daniel Fischer
-
Don Stewart
-
Simon Marlow