Prepare for release of 0.3.9.0

This commit is contained in:
Andrew Martin 2021-11-19 15:52:59 -05:00
parent 4745fe5a43
commit ce52044b08
5 changed files with 49 additions and 17 deletions

View file

@ -5,7 +5,13 @@ Note: Prior to version 0.3.4.0, this library was named
`small-bytearray-builder` is now just a compatibility shim
to ease the migration process.
## 0.3.8.0 -- 2020-??-??
## 0.3.9.0 -- 2021-11-19
* Add `cstring#`
* Add `ToBuilder` and `ToBoundedBuilder` classes
* Add quasiquoter named `bldr` in `Data.Bytes.Builder.Template`.
## 0.3.8.0 -- 2021-06-25
* Fix `doubleDec`, which was encoding small numbers incorrectly.
* Add `runByteString` for producing `ByteString` from bounded builders.

View file

@ -47,7 +47,7 @@ library
Data.Bytes.Chunks
build-depends:
, base >=4.12.0.0 && <5
, byteslice >=0.2.5 && <0.3
, byteslice >=0.2.6 && <0.3
, bytestring >=0.10.8.2 && <0.11
, haskell-src-meta >=0.8
, integer-logarithms >=1.0.3 && <1.1

View file

@ -13,6 +13,7 @@ import Data.Bytes.Builder as B
import Data.Word (Word16)
import Data.Primitive (ByteArray)
import qualified Data.Bytes as Bytes
import qualified Data.Bytes.Text.Ascii
data Word16Tree
= Branch !Word16Tree !Word16Tree
@ -32,7 +33,7 @@ encode (Branch a b) =
B.ascii ')'
expectedSmall :: ByteArray
expectedSmall = Bytes.toByteArray $ Bytes.fromAsciiString
expectedSmall = Bytes.toByteArray $ Data.Bytes.Text.Ascii.fromString
"((AB59,(1F33,2E71)),((((FA9A,247B),890C),(0F13,((55BF,7CF1),389B))),1205))"

View file

@ -2,8 +2,9 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
-- | Quasiquotation for byte builders.
module Data.Bytes.Builder.Template
( templ
( bldr
) where
import Control.Monad (when)
@ -19,9 +20,31 @@ import qualified Data.ByteString.Short as SBS
import qualified Data.Text.Short as TS
import qualified Language.Haskell.TH as TH
templ :: QuasiQuoter
templ = QuasiQuoter
-- | A quasiquoter for builders. Haskell expressions are interpolated
-- with backticks, and the @ToBuilder@ class is used to convert them
-- to builders. Several common escape sequences for whitespace and
-- control characters are recongized. Consider the following expression,
-- where the binding @partition@ has type @Word32@:
--
-- > [templ|[WARN] Partition `partition` has invalid data.\n|]
--
-- This expression has type @Builder@ and expands to:
--
-- > Builder.cstringLen (Ptr "[WARN] Partition "#, 17) <>
-- > Builder.toBuilder partition <>
-- > Builder.cstringLen (Ptr " has invalid data.\n"#, 19)
--
-- The @ToBuilder@ instance for @Word32@ uses decimal encoding, so this
-- would result in the following if @partition@ was 42 (with a newline
-- character at the end):
--
-- > [WARN] Partition 42 has invalid data.
--
-- In the future, a more sophisticated @bbldr@ variant will be added
-- that will support expressions where the maximum length of the entire
-- builder can be computed at compile time.
bldr :: QuasiQuoter
bldr = QuasiQuoter
{ quoteExp = templExp
, quotePat = notHandled "patterns"
, quoteType = notHandled "types"

View file

@ -12,7 +12,7 @@ import Prelude hiding (replicate)
import Control.Applicative (liftA2)
import Control.Monad.ST (runST)
import Data.Bytes.Builder
import Data.Bytes.Builder.Template (templ)
import Data.Bytes.Builder.Template (bldr)
import Data.Bytes.Types (MutableBytes(MutableBytes))
import Data.Char (ord,chr)
import Data.IORef (IORef,newIORef,readIORef,writeIORef)
@ -35,6 +35,8 @@ import qualified Data.Bytes as Bytes
import qualified Data.Bytes.Builder as Builder
import qualified Data.Bytes.Builder.Bounded as Bounded
import qualified Data.Bytes.Chunks as Chunks
import qualified Data.Bytes.Text.Ascii as Ascii
import qualified Data.Bytes.Text.Latin1 as Latin1
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Builder as BB
import qualified Data.ByteString.Lazy.Char8 as LB
@ -294,24 +296,24 @@ tests = testGroup "Tests"
, testGroup "bytes templates"
[ THU.testCase "A" $ do
let name = Just ("foo" :: ShortText)
msgBuilder = [templ|Hello `fromMaybe "World" name`!\n|]
msgBuilder = [bldr|Hello `fromMaybe "World" name`!\n|]
msg = Chunks.concat . Builder.run 200 $ msgBuilder
in Bytes.fromAsciiString "Hello foo!\n" @=? msg
in Ascii.fromString "Hello foo!\n" @=? msg
, THU.testCase "B" $ do
let one = "foo" :: ShortText
two = "bar" :: String
msgBuilder = [templ|`one``two`|]
msgBuilder = [bldr|`one``two`|]
msg = Chunks.concat . Builder.run 200 $ msgBuilder
in Bytes.fromAsciiString "foobar" @=? msg
in Ascii.fromString "foobar" @=? msg
, THU.testCase "C" $ do
let msgBuilder = [templ|a backtick for you: \`|]
let msgBuilder = [bldr|a backtick for you: \`|]
msg = Chunks.concat . Builder.run 200 $ msgBuilder
in Bytes.fromAsciiString "a backtick for you: `" @=? msg
in Ascii.fromString "a backtick for you: `" @=? msg
, THU.testCase "D" $ do
let i = 137 :: Int
msgBuilder = [templ|there are `i` lights!|]
msgBuilder = [bldr|there are `i` lights!|]
msg = Chunks.concat . Builder.run 200 $ msgBuilder
in Bytes.fromAsciiString "there are 137 lights!" @=? msg
in Ascii.fromString "there are 137 lights!" @=? msg
]
]
@ -362,7 +364,7 @@ newtype AsciiByteArray = AsciiByteArray ByteArray
instance Show AsciiByteArray where
show (AsciiByteArray b) = if Bytes.all (\w -> w >= 32 && w < 127) (Bytes.fromByteArray b)
then Bytes.toLatinString (Bytes.fromByteArray b)
then Latin1.toString (Bytes.fromByteArray b)
else show (show b)
instance Arbitrary Word128 where