[web-devel] Data.Word8 (word8 library)

Lennart Kolmodin kolmodin at gmail.com
Thu Sep 20 11:57:17 CEST 2012


Here are the methods in question:

-- | Conversion between 'Word8' and 'Char'. Should compile to a
no-op.w2c :: Word8 -> Char#if !defined(__GLASGOW_HASKELL__)w2c = chr .
fromIntegral#elsew2c = unsafeChr . fromIntegral#endif{-# INLINE w2c
#-}-- | Unsafe conversion between 'Char' and 'Word8'. This is a no-op
and-- silently truncates to 8 bits Chars > '\255'. It is provided as--
convenience for ByteString construction.c2w :: Char -> Word8c2w =
fromIntegral . ord{-# INLINE c2w #-}

They should both be harmless, according to the docs.


2012/9/20 Johan Tibell <johan.tibell at gmail.com>

> On Thu, Sep 20, 2012 at 10:41 AM, Kazu Yamamoto <kazu at iij.ad.jp> wrote:
> > Why do people use Data.ByteString.Char8? I guess that there are two
> > reasons:
> >
> > - There are no standard utility functions for Word8 such as "isUpper"
> > - Numeric literal (e.g 72 for 'H') is not readable
>
> The Char8 module was added so that it's easier to work with protocols
> that mix binary and ASCII data, such as HTTP.
>
> Note that Word8 is represented using a full machine word, just like
> Char, so you're unlikely to get any performance improvements from
> Word8 in this case (unless GHC fails to simplify e.g. calls to 'ord'
> and 'chr' in places).
>
> -- Johan
>
> _______________________________________________
> web-devel mailing list
> web-devel at haskell.org
> http://www.haskell.org/mailman/listinfo/web-devel
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/web-devel/attachments/20120920/a7278345/attachment.htm>


More information about the web-devel mailing list