{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS_HADDOCK prune #-}
module Core.Text.Bytes
( Bytes
, emptyBytes
, packBytes
, Binary (fromBytes, intoBytes)
, hOutput
, hInput
, unBytes
) where
import qualified Data.ByteString as B
( ByteString
, empty
, hGetContents
, hPut
, pack
, unpack
)
import qualified Data.ByteString.Builder as B (Builder, byteString, toLazyByteString)
import qualified Data.ByteString.Char8 as C
( pack
)
import qualified Data.ByteString.Lazy as L (ByteString, fromStrict, toStrict)
import Data.Hashable (Hashable)
import Data.Word (Word8)
import GHC.Generics (Generic)
import System.IO (Handle)
newtype Bytes
= StrictBytes B.ByteString
deriving (Int -> Bytes -> ShowS
[Bytes] -> ShowS
Bytes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bytes] -> ShowS
$cshowList :: [Bytes] -> ShowS
show :: Bytes -> String
$cshow :: Bytes -> String
showsPrec :: Int -> Bytes -> ShowS
$cshowsPrec :: Int -> Bytes -> ShowS
Show, Bytes -> Bytes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bytes -> Bytes -> Bool
$c/= :: Bytes -> Bytes -> Bool
== :: Bytes -> Bytes -> Bool
$c== :: Bytes -> Bytes -> Bool
Eq, Eq Bytes
Bytes -> Bytes -> Bool
Bytes -> Bytes -> Ordering
Bytes -> Bytes -> Bytes
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Bytes -> Bytes -> Bytes
$cmin :: Bytes -> Bytes -> Bytes
max :: Bytes -> Bytes -> Bytes
$cmax :: Bytes -> Bytes -> Bytes
>= :: Bytes -> Bytes -> Bool
$c>= :: Bytes -> Bytes -> Bool
> :: Bytes -> Bytes -> Bool
$c> :: Bytes -> Bytes -> Bool
<= :: Bytes -> Bytes -> Bool
$c<= :: Bytes -> Bytes -> Bool
< :: Bytes -> Bytes -> Bool
$c< :: Bytes -> Bytes -> Bool
compare :: Bytes -> Bytes -> Ordering
$ccompare :: Bytes -> Bytes -> Ordering
Ord, forall x. Rep Bytes x -> Bytes
forall x. Bytes -> Rep Bytes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bytes x -> Bytes
$cfrom :: forall x. Bytes -> Rep Bytes x
Generic)
unBytes :: Bytes -> B.ByteString
unBytes :: Bytes -> ByteString
unBytes (StrictBytes ByteString
b') = ByteString
b'
{-# INLINE unBytes #-}
instance Hashable Bytes
class Binary α where
fromBytes :: Bytes -> α
intoBytes :: α -> Bytes
instance Binary Bytes where
fromBytes :: Bytes -> Bytes
fromBytes = forall a. a -> a
id
intoBytes :: Bytes -> Bytes
intoBytes = forall a. a -> a
id
instance Binary B.ByteString where
fromBytes :: Bytes -> ByteString
fromBytes (StrictBytes ByteString
b') = ByteString
b'
intoBytes :: ByteString -> Bytes
intoBytes ByteString
b' = ByteString -> Bytes
StrictBytes ByteString
b'
instance Binary L.ByteString where
fromBytes :: Bytes -> ByteString
fromBytes (StrictBytes ByteString
b') = ByteString -> ByteString
L.fromStrict ByteString
b'
intoBytes :: ByteString -> Bytes
intoBytes ByteString
b' = ByteString -> Bytes
StrictBytes (ByteString -> ByteString
L.toStrict ByteString
b')
instance Binary B.Builder where
fromBytes :: Bytes -> Builder
fromBytes (StrictBytes ByteString
b') = ByteString -> Builder
B.byteString ByteString
b'
intoBytes :: Builder -> Bytes
intoBytes Builder
b' = ByteString -> Bytes
StrictBytes (ByteString -> ByteString
L.toStrict (Builder -> ByteString
B.toLazyByteString Builder
b'))
instance Binary [Word8] where
fromBytes :: Bytes -> [Word8]
fromBytes (StrictBytes ByteString
b') = ByteString -> [Word8]
B.unpack ByteString
b'
intoBytes :: [Word8] -> Bytes
intoBytes = ByteString -> Bytes
StrictBytes forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
B.pack
emptyBytes :: Bytes
emptyBytes :: Bytes
emptyBytes = ByteString -> Bytes
StrictBytes ByteString
B.empty
packBytes :: String -> Bytes
packBytes :: String -> Bytes
packBytes = ByteString -> Bytes
StrictBytes forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
C.pack
hOutput :: Handle -> Bytes -> IO ()
hOutput :: Handle -> Bytes -> IO ()
hOutput Handle
handle (StrictBytes ByteString
b') = Handle -> ByteString -> IO ()
B.hPut Handle
handle ByteString
b'
hInput :: Handle -> IO Bytes
hInput :: Handle -> IO Bytes
hInput Handle
handle = do
ByteString
contents <- Handle -> IO ByteString
B.hGetContents Handle
handle
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Bytes
StrictBytes ByteString
contents)