{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Data.ByteString.Base64.Lazy.Type (
ByteString64,
makeByteString64,
getByteString64,
mkBS64,
getBS64,
getEncodedByteString64,
) where
import Prelude ()
import Prelude.Compat
import Control.DeepSeq (NFData (..))
import Data.Aeson
(FromJSON (..), FromJSONKey (..), ToJSON (..), ToJSONKey (..), withText)
import Data.Aeson.Types (FromJSONKeyFunction (..), toJSONKeyText)
import Data.Binary (Binary (..))
import Data.ByteString.Lazy (ByteString, pack, unpack)
import Data.Data (Data, Typeable)
import Data.Hashable (Hashable)
import Data.Semigroup (Semigroup (..))
import Data.String (IsString (..))
import Data.Text.Lazy (fromStrict, toStrict)
import Data.Text.Lazy.Encoding (decodeLatin1, encodeUtf8)
import GHC.Generics (Generic)
import Test.QuickCheck
(Arbitrary (..), CoArbitrary (..), Function (..), functionMap,
shrinkMap)
import qualified Data.ByteString.Base64.Lazy as Base64
#ifdef MIN_VERSION_cereal
import Data.Serialize (Serialize)
#endif
#ifdef MIN_VERSION_serialise
import Codec.Serialise (Serialise (..))
#endif
newtype ByteString64 = BS64 ByteString
deriving (Eq, Ord, Data, Typeable, Generic)
instance Show ByteString64 where
showsPrec d (BS64 bs) = showParen (d > 10) $ showString "mkBS64 " . showsPrec 11 bs
makeByteString64 :: ByteString -> ByteString64
makeByteString64 = BS64
mkBS64 :: ByteString -> ByteString64
mkBS64 = makeByteString64
getByteString64 :: ByteString64 -> ByteString
getByteString64 = \(BS64 bs) -> bs
getBS64 :: ByteString64 -> ByteString
getBS64 = \(BS64 bs) -> bs
getEncodedByteString64 :: ByteString64 -> ByteString
getEncodedByteString64 = Base64.encode . getBS64
instance IsString ByteString64 where
fromString = BS64 . fromString
instance Semigroup ByteString64 where
BS64 a <> BS64 b = BS64 (a <> b)
instance Monoid ByteString64 where
mempty = BS64 mempty
mappend = (<>)
instance NFData ByteString64 where
rnf = rnf' . getBS64 where
#if MIN_VERSION_bytestring(0,10,0)
rnf' = rnf
#else
rnf' Empty = ()
rnf' (Chunk _ b) = rnf' b
#endif
instance Hashable ByteString64
instance ToJSON ByteString64 where
toJSON = toJSON . decodeLatin1 . getEncodedByteString64
toEncoding = toEncoding . decodeLatin1 . getEncodedByteString64
instance FromJSON ByteString64 where
parseJSON = withText "ByteString" $
either fail (pure . BS64) . Base64.decode . encodeUtf8 . fromStrict
instance ToJSONKey ByteString64 where
toJSONKey = toJSONKeyText (toStrict . decodeLatin1 . getEncodedByteString64)
instance FromJSONKey ByteString64 where
fromJSONKey = FromJSONKeyTextParser $
either fail (pure . BS64) . Base64.decode . encodeUtf8 . fromStrict
#ifdef MIN_VERSION_cereal
instance Serialize ByteString64
#endif
instance Binary ByteString64 where
put = put . getBS64
get = fmap makeByteString64 get
#ifdef MIN_VERSION_serialise
instance Serialise ByteString64 where
encode = encode . getBS64
decode = fmap makeByteString64 decode
#endif
instance Arbitrary ByteString64 where
arbitrary = BS64 . pack <$> arbitrary
shrink = shrinkMap (BS64 . pack) (unpack . getBS64)
instance CoArbitrary ByteString64 where
coarbitrary = coarbitrary . unpack . getBS64
instance Function ByteString64 where
function = functionMap (unpack . getBS64) (BS64 . pack)