File: Base16.hs

package info (click to toggle)
haskell-base16-bytestring 1.0.2.0-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 100 kB
  • sloc: haskell: 385; makefile: 2
file content (107 lines) | stat: -rw-r--r-- 3,192 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
-- |
-- Module      : Data.ByteString.Base16
-- Copyright   : (c) 2011 MailRank, Inc.
--
-- License     : BSD
-- Maintainer  : Herbert Valerio Riedel <hvr@gnu.org>,
--               Mikhail Glushenkov <mikhail.glushenkov@gmail.com>,
--               Emily Pillmore <emilypi@cohomolo.gy>
-- Stability   : stable
-- Portability : non-portable
--
-- RFC 4648-compliant Base16 (Hexadecimal) encoding for 'ByteString' values.
-- For a complete Base16 encoding specification, please see <https://tools.ietf.org/html/rfc4648#section-8 RFC-4648 section 8>.
--
module Data.ByteString.Base16
( encode
, decode
, decodeLenient
) where

import Data.ByteString (empty)
import Data.ByteString.Base16.Internal (encodeLoop, decodeLoop, lenientLoop, mkBS, withBS)
import Data.ByteString.Internal (ByteString)

import Foreign.ForeignPtr (withForeignPtr)
import Foreign.Ptr (plusPtr)

import GHC.ForeignPtr (mallocPlainForeignPtrBytes)

-- | Encode a 'ByteString' value in base16 (i.e. hexadecimal).
-- Encoded values will always have a length that is a multiple of 2.
--
-- === __Examples__:
--
-- > encode "foo"  == "666f6f"
--
encode :: ByteString -> ByteString
encode bs = withBS bs go
  where
    go !sptr !slen
      | slen > maxBound `div` 2 =
        error "Data.ByteString.Base16.encode: input too long"
      | otherwise = do
          let l = slen * 2
          dfp <- mallocPlainForeignPtrBytes l
          withForeignPtr dfp $ \dptr ->
            encodeLoop dptr sptr (sptr `plusPtr` slen)
          return $ mkBS dfp l

-- | Decode a base16-encoded 'ByteString' value.
-- If errors are encountered during the decoding process,
-- then an error message and character offset will be returned in
-- the @Left@ clause of the coproduct.
--
-- === __Examples__:
--
-- > decode "666f6f"  == Right "foo"
-- > decode "66quux"  == Left "invalid character at offset: 2"
-- > decode "666quux" == Left "invalid character at offset: 3"
--
-- @since 1.0.0.0
--
decode :: ByteString -> Either String ByteString
decode bs = withBS bs go
  where
    go !sptr !slen
      | slen == 0 = return $ Right empty
      | r /= 0 = return $ Left "invalid bytestring size"
      | otherwise = do
        dfp <- mallocPlainForeignPtrBytes q
        withForeignPtr dfp $ \dptr ->
          decodeLoop dfp dptr sptr (plusPtr sptr slen)
      where
        !q = slen `quot` 2
        !r = slen `rem` 2

-- | Decode a Base16-encoded 'ByteString' value leniently, using a
-- strategy that never fails.
--
-- /N.B./: this is not RFC 4648-compliant
--
-- === __Examples__:
--
-- > decodeLenient "666f6f"  == "foo"
-- > decodeLenient "66quuxx" == "f"
-- > decodeLenient "666quux" == "f"
-- > decodeLenient "666fquu" -- "fo"
--
-- @since 1.0.0.0
--
decodeLenient :: ByteString -> ByteString
decodeLenient bs = withBS bs go
  where
    go !sptr !slen
      | slen == 0 = return empty
      | otherwise = do
        dfp <- mallocPlainForeignPtrBytes (q * 2)
        withForeignPtr dfp $ \dptr ->
          lenientLoop dfp dptr sptr (plusPtr sptr slen)
      where
        !q = slen `quot` 2