[Haskell-cafe] How to put a string into Data.Binary.Put

Daniel Fischer daniel.is.fischer at web.de
Sat Nov 6 08:54:20 EDT 2010


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.



More information about the Haskell-Cafe mailing list