{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeApplications #-}
module Data.ByteString.Multibase
(
BaseN.Base(..)
, ToCode
, Multibase
, fromMultibase
, encodedBytes
, encode
, decode
, CompactMultibase
, compact
, expand
)
where
import Control.DeepSeq (NFData)
import Data.ByteString (ByteString)
import Data.ByteString.BaseN (AtBase, ValidBase)
import qualified Data.ByteString.BaseN as BaseN
import qualified Data.ByteString.Char8 as C8
import Data.ByteString.Short (ShortByteString, fromShort, toShort)
import Data.Coerce (coerce)
import Data.Hashable (Hashable)
import Data.Typeable
class ValidBase b => ToCode b where
toCode :: proxy b -> Char
instance ToCode "id" where
toCode = const '\000'
instance ToCode "16" where
toCode = const 'f'
instance ToCode "16u" where
toCode = const 'F'
instance ToCode "32x" where
toCode = const 'v'
instance ToCode "32xu" where
toCode = const 'V'
instance ToCode "32xp" where
toCode = const 't'
instance ToCode "32xpu" where
toCode = const 'T'
instance ToCode "32" where
toCode = const 'b'
instance ToCode "32z" where
toCode = const 'h'
instance ToCode "32u" where
toCode = const 'B'
instance ToCode "32p" where
toCode = const 'c'
instance ToCode "32pu" where
toCode = const 'C'
instance ToCode "58flickr" where
toCode = const 'Z'
instance ToCode "58btc" where
toCode = const 'z'
instance ToCode "64" where
toCode = const 'm'
instance ToCode "64p" where
toCode = const 'M'
instance ToCode "64url" where
toCode = const 'u'
instance ToCode "64urlpad" where
toCode = const 'U'
fromCode :: Char -> Maybe (ByteString -> Either String ByteString)
fromCode '\000' = pure pure
fromCode 'f' = pure (BaseN.decodeAtBaseEither (Proxy @"16"))
fromCode 'F' = pure (BaseN.decodeAtBaseEither (Proxy @"16u"))
fromCode 'v' = pure (BaseN.decodeAtBaseEither (Proxy @"32x"))
fromCode 'V' = pure (BaseN.decodeAtBaseEither (Proxy @"32xu"))
fromCode 't' = pure (BaseN.decodeAtBaseEither (Proxy @"32xp"))
fromCode 'T' = pure (BaseN.decodeAtBaseEither (Proxy @"32xpu"))
fromCode 'b' = pure (BaseN.decodeAtBaseEither (Proxy @"32"))
fromCode 'h' = pure (BaseN.decodeAtBaseEither (Proxy @"32z"))
fromCode 'B' = pure (BaseN.decodeAtBaseEither (Proxy @"32u"))
fromCode 'c' = pure (BaseN.decodeAtBaseEither (Proxy @"32p"))
fromCode 'C' = pure (BaseN.decodeAtBaseEither (Proxy @"32pu"))
fromCode 'Z' = pure (BaseN.decodeAtBaseEither (Proxy @"58flickr"))
fromCode 'z' = pure (BaseN.decodeAtBaseEither (Proxy @"58btc"))
fromCode 'm' = pure (BaseN.decodeAtBaseEither (Proxy @"64"))
fromCode 'M' = pure (BaseN.decodeAtBaseEither (Proxy @"64p"))
fromCode 'u' = pure (BaseN.decodeAtBaseEither (Proxy @"64url"))
fromCode 'U' = pure (BaseN.decodeAtBaseEither (Proxy @"64urlpad"))
fromCode _ = Nothing
newtype Multibase = Multibase ByteString
deriving (Eq, Ord, Hashable, NFData)
newtype CompactMultibase = Compact ShortByteString
deriving (Eq, Ord, Hashable, NFData)
fromMultibase :: Multibase -> ByteString
fromMultibase = coerce
encodedBytes :: Multibase -> ByteString
encodedBytes = C8.tail . coerce
encode :: ToCode b => AtBase b -> Multibase
encode base = coerce . C8.cons (toCode base) . BaseN.encodedBytes $ base
decode :: ByteString -> Either String ByteString
decode bs = do
(c, bs') <- note "Empty input" $ C8.uncons bs
case fromCode c of
Just decodeIt -> decodeIt bs'
Nothing -> Left $ "Unknown encoding " <> show c
compact :: Multibase -> CompactMultibase
compact = coerce . toShort . coerce
{-# INLINE compact #-}
expand :: CompactMultibase -> Multibase
expand = coerce . fromShort . coerce
{-# INLINE expand #-}
note :: a -> Maybe b -> Either a b
note a = maybe (Left a) pure