{- Copyright 2014 Mario Blazevic License: BSD3 (see BSD3-LICENSE.txt file) -} -- | This module defines the 'ByteStringUTF8' newtype wrapper around 'ByteString', together with its 'TextualMonoid' -- instance. -- {-# LANGUAGE BangPatterns #-} module Data.Monoid.Instances.ByteString.Char8 () where import Data.ByteString.Char8 (ByteString) import qualified Data.ByteString.Char8 as ByteString.Char8 import qualified Data.ByteString as B import qualified Data.ByteString.Internal as B import qualified Data.ByteString.Unsafe as B import Data.Monoid.Textual (TextualMonoid(..)) instance TextualMonoid ByteString where singleton = ByteString.Char8.singleton splitCharacterPrefix bs = ByteString.Char8.uncons bs foldl _ft fc a0 bs = ByteString.Char8.foldl fc a0 bs foldl' _ft fc a0 bs = ByteString.Char8.foldl' fc a0 bs {-# INLINE foldl' #-} foldr _ft fc a0 bs = ByteString.Char8.foldr fc a0 bs {-# INLINE foldr #-} dropWhile _pt pc bs = ByteString.Char8.dropWhile pc bs {-# INLINE dropWhile #-} takeWhile _pt pc bs = ByteString.Char8.takeWhile pc bs {-# INLINE takeWhile #-} span _pt pc bs = ByteString.Char8.span pc bs {-# INLINE span #-} break _pt pc bs = ByteString.Char8.break pc bs {-# INLINE break #-} spanMaybe s0 _fb fc bs = let inner !i !s | i < len = case fc s (B.w2c $ B.unsafeIndex bs i) of Just s' -> inner (i + 1) s' _ -> done i s | otherwise = done i s done !i !s = (B.unsafeTake i bs, B.unsafeDrop i bs, s) !len = B.length bs in inner 0 s0 {-# INLINE spanMaybe #-}