How to put a string into Data.Binary.Put

Hi, I was trying to put a String in a ByteString import qualified Data.ByteString.Lazy as BS message :: BS.ByteString message = runPut $ do let string="SOME STRING" map (putWord8.fromIntegral.ord) string -- this ofcourse generates [Put] How can I convert the list of Put's such that it could be used in the Put monad? For now I used the workaround of first converting the string to ByteString like this - stringToByteString :: String -> BS.ByteString stringToByteString str = BS.pack (map (fromIntegral.ord) str) and then using putLazyByteString inside the Put monad. -- Regards, Kashyap

On Saturday 06 November 2010 13:30:45, C K Kashyap wrote:
Hi, I was trying to put a String in a ByteString
import qualified Data.ByteString.Lazy as BS message :: BS.ByteString message = runPut $ do let string="SOME STRING" map (putWord8.fromIntegral.ord) string -- this ofcourse generates [Put]
You'd want mapM_ (putWord8 . fromIntegral . ord)
How can I convert the list of Put's such that it could be used in the Put monad?
sequence_ :: Monad m => [m a] -> m () if you want to use the results of the monadic actions, sequence :: Monad m => [m a] -> m [a] Often sequence and sequence_ are used for list resulting from a map, so there's mapM_ :: Monad m => (a -> m b) -> [a] -> m () mapM_ f xs = sequence_ (map f xs) mapM :: Monad m => (a -> m b) -> [a] -> m [b] mapM f xs = sequence (map f xs)
For now I used the workaround of first converting the string to ByteString like this -
stringToByteString :: String -> BS.ByteString stringToByteString str = BS.pack (map (fromIntegral.ord) str)
and then using putLazyByteString inside the Put monad.

Thanks a lot Gregory and Daniel, I think I'll go with the "mapM_ (putWord8 . fromIntegral . ord)" approach. -- Regards, Kashyap

On 11/6/10 6:38 AM, C K Kashyap wrote:
Thanks a lot Gregory and Daniel,
I think I'll go with the "mapM_ (putWord8 . fromIntegral . ord)" approach.
If your string has any chance of containing Unicode characters then you will want to use the "encode" function in the module "Codec.Binary.UTF8.String" in the package "utf8-string", so that the code becomes mapM_ putWord8 . encode Cheers, Greg

Use one of the Char8 modules, depending on whether you want a strict
or lazy bytestring:
-----------------------------------------------------------------------
import qualified Data.ByteString.Lazy.Char8 as BS
message :: BS.ByteString
message = BS.pack "SOME STRING"
-----------------------------------------------------------------------
See the docs at:
http://hackage.haskell.org/packages/archive/bytestring/0.9.1.7/doc/html/Data...
http://hackage.haskell.org/packages/archive/bytestring/0.9.1.7/doc/html/Data...
mapping over putWord8 is much slower than putting a single bytestring;
if you want to put a string, pack it first:
-----------------------------------------------------------------------
putString :: String -> Put
putString str = putLazyByteString (BS.pack str)
-- alternative: probably faster
import qualified Data.ByteString.Char8 as B
putString :: String -> Put
putString str = putByteString (B.pack str)
-----------------------------------------------------------------------
On Sat, Nov 6, 2010 at 05:30, C K Kashyap
Hi, I was trying to put a String in a ByteString
import qualified Data.ByteString.Lazy as BS message :: BS.ByteString message = runPut $ do let string="SOME STRING" map (putWord8.fromIntegral.ord) string -- this ofcourse generates [Put]
How can I convert the list of Put's such that it could be used in the Put monad?
For now I used the workaround of first converting the string to ByteString like this -
stringToByteString :: String -> BS.ByteString stringToByteString str = BS.pack (map (fromIntegral.ord) str)
and then using putLazyByteString inside the Put monad.
-- Regards, Kashyap _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
C K Kashyap
-
Daniel Fischer
-
Gregory Crosswhite
-
John Millikin