{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Internal
( module Internal
, ByteString
, ShortByteString
, ShortText
, T.Text
, Proxy(..)
, NFData(rnf), force
, UTCTime
, Hashable
, ap
) where
import qualified Codec.Base16 as B16
import qualified Codec.Base64 as B64
import Control.DeepSeq
import Control.Monad (ap)
import qualified Crypto.Hash.MD5 as MD5
import qualified Crypto.Hash.SHA256 as SHA256
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BC8
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Internal
import Data.ByteString.Short (ShortByteString, fromShort,
toShort)
import qualified Data.ByteString.Short as SBS
import Data.Hashable
import Data.Proxy
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Text.Short (ShortText)
import Data.Time (UTCTime)
newtype SHA256Val = SHA256Val ShortByteString
deriving (Eq,Ord,Hashable,NFData,Typeable)
instance Show SHA256Val where
show = show . sha256hex
sha256hash :: BL.ByteString -> SHA256Val
sha256hash = SHA256Val . toShort . SHA256.hashlazy
sha256hex :: SHA256Val -> ByteString
sha256hex (SHA256Val x) = B16.encode (fromShort x)
newtype MD5Val = MD5Val ShortByteString
deriving (Eq,Ord,Hashable,NFData,Typeable)
instance Show MD5Val where
show = show . md5hex
instance IsString MD5Val where
fromString = fromMaybe (error "invalid MD5Val string-literal") . md5unhex . fromString
md5hash :: BL.ByteString -> MD5Val
md5hash = MD5Val . toShort . MD5.hashlazy
md5hex :: MD5Val -> ByteString
md5hex (MD5Val x) = B16.encode x
md5b64 :: MD5Val -> ByteString
md5b64 (MD5Val x) = B64.encode x
md5unhex :: ByteString -> Maybe MD5Val
md5unhex x = case B16.decode x of
Right d -> md5FromSBS d
_ -> Nothing
md5ToSBS :: MD5Val -> ShortByteString
md5ToSBS (MD5Val x) = x
md5FromSBS :: ShortByteString -> Maybe MD5Val
md5FromSBS d | SBS.length d == 16 = Just (MD5Val d)
| otherwise = Nothing
md5zero :: MD5Val
md5zero = MD5Val $ toShort $ BS.replicate 16 0
strictPair :: a -> b -> (a,b)
strictPair !a !b = (a,b)
urlEncode :: Bool -> ByteString -> ByteString
urlEncode escapeSlash = BC8.concatMap go
where
go c | inRng '0' '9' c ||
inRng 'a' 'z' c ||
inRng 'A' 'Z' c ||
c `elem` ['-','_','.','~'] = BC8.singleton c
| c == '/' = if escapeSlash then "%2F" else BC8.singleton c
| otherwise = let (h,l) = quotRem (fromIntegral $ fromEnum c) 0x10
in BS.pack [0x25, hex h, hex l]
inRng x y c = c >= x && c <= y
hex j | j < 10 = 0x30 + j
| otherwise = 0x37 + j
urlDecodeTextUtf8 :: Text -> Maybe Text
urlDecodeTextUtf8 t0
| (_,[]) <- chunks = Just t'
| all ((==2) . T.length . fst) (snd chunks) = T.concat <$> mchunks3
| otherwise = Nothing
where
mchunks3 = h chunks2
where
h (c1,cs) = (:) c1 . mconcat <$> mapM go cs
go :: (Text,Text) -> Maybe [Text]
go (x,y) = do x' <- e2m (B16.decode x)
x'' <- e2m (T.decodeUtf8' x')
pure [x'', y]
chunks2 = compact [] <$> chunks
compact acc [] = [(T.concat (reverse acc),"") | not (null acc) ]
compact acc ((octet,""):rest) = compact (octet:acc) rest
compact acc ((octet,chunk):rest)
| null acc = (octet,chunk) : compact [] rest
| otherwise = (T.concat (reverse (octet:acc)),chunk) : compact [] rest
chunks = case T.splitOn "%" t' of
[] -> undefined
[_] -> (t0,[])
(x:xs) -> (x,fmap (T.splitAt 2) xs)
t' | T.any (=='+') t0 = T.map (\c -> if c == '+' then ' ' else c) t0
| otherwise = t0
e2m :: Either a1 a2 -> Maybe a2
e2m = either (\_->Nothing) Just
mkChunk :: ByteString -> BL.ByteString -> BL.ByteString
mkChunk bs bl
| BS.null bs = bl
| otherwise = Data.ByteString.Lazy.Internal.Chunk bs bl