-- |
-- Module      : Data.TypeID.Internal
-- License     : MIT
-- Maintainer  : mmzk1526@outlook.com
-- Portability : GHC
--
module Data.TypeID.Internal where

import           Control.Exception
import           Control.Monad
import           Control.Monad.IO.Class
import           Control.Monad.ST
import           Data.Aeson.Types hiding (Array, String)
import           Data.Array
import           Data.Array.ST
import           Data.Array.Unsafe (unsafeFreeze)
import           Data.Binary
import           Data.Binary.Get
import           Data.Binary.Put
import           Data.Bifunctor
import           Data.Bits
import qualified Data.ByteString as BS
import           Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString.Lazy as BSL
import           Data.Char
import           Data.Hashable
import           Data.Proxy
import           Data.String
import           Data.Text (Text)
import qualified Data.Text as T
import           Data.Text.Encoding
import           Data.TypeID.Class
import           Data.TypeID.Error
import           Data.UUID.Types.Internal (UUID(..))
import qualified Data.UUID.Types.Internal as UUID
import qualified Data.UUID.V1 as V1
import qualified Data.UUID.V4 as V4
import qualified Data.UUID.V5 as V5
import qualified Data.UUID.V7 as V7
import           Data.UUID.Versions
import           System.Random
import           Foreign

-- | This data type also supports 'Data.TypeID.V7.TypeID's with 'UUID' versions
-- other than v7.
--
--  The constructor is not exposed to the public API to prevent generating
-- invalid 'TypeID''s.
data TypeID' (version :: UUIDVersion) = TypeID' Text UUID
  deriving (TypeID' version -> TypeID' version -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
/= :: TypeID' version -> TypeID' version -> Bool
$c/= :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
== :: TypeID' version -> TypeID' version -> Bool
$c== :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
Eq, TypeID' version -> TypeID' version -> Bool
TypeID' version -> TypeID' version -> Ordering
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
forall (version :: UUIDVersion). Eq (TypeID' version)
forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Ordering
forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> TypeID' version
min :: TypeID' version -> TypeID' version -> TypeID' version
$cmin :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> TypeID' version
max :: TypeID' version -> TypeID' version -> TypeID' version
$cmax :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> TypeID' version
>= :: TypeID' version -> TypeID' version -> Bool
$c>= :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
> :: TypeID' version -> TypeID' version -> Bool
$c> :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
<= :: TypeID' version -> TypeID' version -> Bool
$c<= :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
< :: TypeID' version -> TypeID' version -> Bool
$c< :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Bool
compare :: TypeID' version -> TypeID' version -> Ordering
$ccompare :: forall (version :: UUIDVersion).
TypeID' version -> TypeID' version -> Ordering
Ord)

instance Show (TypeID' version) where
  show :: TypeID' version -> String
  show :: TypeID' version -> String
show = forall (version :: UUIDVersion). TypeID' version -> String
toString
  {-# INLINE show #-}

instance Read (TypeID' version) where
  readsPrec :: Int -> String -> [(TypeID' version, String)]
  readsPrec :: Int -> ReadS (TypeID' version)
readsPrec Int
_ String
str = case forall (version :: UUIDVersion).
String -> Either TypeIDError (TypeID' version, String)
parseStringS String
str of
    Left TypeIDError
_       -> []
    Right (TypeID' version
x, String
y) -> [(TypeID' version
x, String
y)]
  {-# INLINE readsPrec #-}

instance ToJSON (TypeID' version) where
  toJSON :: TypeID' version -> Value
  toJSON :: TypeID' version -> Value
toJSON = forall a. ToJSON a => a -> Value
toJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (version :: UUIDVersion). TypeID' version -> Text
toText
  {-# INLINE toJSON #-}

instance FromJSON (TypeID' version) where
  parseJSON :: Value -> Parser (TypeID' version)
  parseJSON :: Value -> Parser (TypeID' version)
parseJSON Value
str = do
    Text
s <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
str
    case forall (version :: UUIDVersion).
Text -> Either TypeIDError (TypeID' version)
parseText Text
s of
      Left TypeIDError
err  -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show TypeIDError
err
      Right TypeID' version
tid -> forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeID' version
tid
  {-# INLINE parseJSON #-}

instance ToJSONKey (TypeID' version) where
  toJSONKey :: ToJSONKeyFunction (TypeID' version)
  toJSONKey :: ToJSONKeyFunction (TypeID' version)
toJSONKey = forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText forall (version :: UUIDVersion). TypeID' version -> Text
toText
  {-# INLINE toJSONKey #-}

instance FromJSONKey (TypeID' version) where
  fromJSONKey :: FromJSONKeyFunction (TypeID' version)
  fromJSONKey :: FromJSONKeyFunction (TypeID' version)
fromJSONKey = forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser \Text
t -> case forall (version :: UUIDVersion).
Text -> Either TypeIDError (TypeID' version)
parseText Text
t of
    Left TypeIDError
err  -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show TypeIDError
err
    Right TypeID' version
tid -> forall (f :: * -> *) a. Applicative f => a -> f a
pure TypeID' version
tid
  {-# INLINE fromJSONKey #-}

-- | Since the specification does not formulate a concrete binary format, this
-- instance is based on the following custom format:
--
-- * The first 16 bytes are the suffix 'UUID' encoded in base32.
-- * The next byte is the length of the prefix encoded in a byte.
-- * The next bytes are the prefix, each letter taking 5 bits, mapping \'a\' to
--   1 and \'z\' to 26.
--
-- Note that the prefix and the 'UUID' is swapped compared to the string
-- representation, this is for the convenience of the use case where only the
-- suffix 'UUID' is required. Because of this, the sorting order may be
-- different from the string representation, but they are guaranteed to be the
-- same if the same prefix is used.
instance Binary (TypeID' version) where
  put :: TypeID' version -> Put
  put :: TypeID' version -> Put
put (TypeID' Text
prefix UUID
uuid) = do
    forall t. Binary t => t -> Put
put UUID
uuid
    let encodedPrefix :: [Word8]
encodedPrefix = [Word8] -> [Word8]
concat5BitInts forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Num a => a -> a -> a
subtract Word8
96) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
BS.unpack
                      forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
prefix
    Word8 -> Put
putWord8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word8]
encodedPrefix
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [Word8]
encodedPrefix Word8 -> Put
putWord8
  {-# INLINE put #-}

  get :: Get (TypeID' version)
  get :: Get (TypeID' version)
get = do
    UUID
uuid          <- forall t. Binary t => Get t
get
    Word8
len           <- Get Word8
getWord8
    [Word8]
encodedPrefix <- [Word8] -> [Word8]
separate5BitInts forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
len) Get Word8
getWord8
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word8]
encodedPrefix forall a. Ord a => a -> a -> Bool
> Int
63) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary: Prefix too long"
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Bool -> Bool -> Bool
(&&) (forall a. Ord a => a -> a -> Bool
< Word8
1) (forall a. Ord a => a -> a -> Bool
> Word8
25)) [Word8]
encodedPrefix)
         (forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Binary: Invalid prefix")
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' (ByteString -> Text
decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
BS.pack forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Num a => a -> a -> a
+ Word8
96) [Word8]
encodedPrefix) UUID
uuid
  {-# INLINE get #-}

-- | Similar to the 'Binary' instance, but the 'UUID' is stored in host endian.
instance Storable (TypeID' version) where
  sizeOf :: TypeID' version -> Int
  sizeOf :: TypeID' version -> Int
sizeOf TypeID' version
_ = Int
60
  {-# INLINE sizeOf #-}

  alignment :: TypeID' version -> Int
  alignment :: TypeID' version -> Int
alignment TypeID' version
_ = Int
4
  {-# INLINE alignment #-}

  peek :: Ptr (TypeID' version) -> IO (TypeID' version)
  peek :: Ptr (TypeID' version) -> IO (TypeID' version)
peek Ptr (TypeID' version)
ptr = do
    UUID
uuid          <- forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Ptr b
castPtr Ptr (TypeID' version)
ptr :: Ptr UUID)
    Int
len           <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr (TypeID' version)
ptr Int
16 :: IO Word8)
    [Word8]
encodedPrefix <- [Word8] -> [Word8]
separate5BitInts
                 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [Int
1..Int
len] \Int
ix -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff @Word8 Ptr (TypeID' version)
ptr (Int
16 forall a. Num a => a -> a -> a
+ Int
ix)
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word8]
encodedPrefix forall a. Ord a => a -> a -> Bool
> Int
63) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Storable: Prefix too long"
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Bool -> Bool -> Bool
(&&) (forall a. Ord a => a -> a -> Bool
< Word8
1) (forall a. Ord a => a -> a -> Bool
> Word8
25)) [Word8]
encodedPrefix)
         (forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Storable: Invalid prefix")
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' (ByteString -> Text
decodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
BS.pack forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Num a => a -> a -> a
+ Word8
96) [Word8]
encodedPrefix) UUID
uuid
  {-# INLINE peek #-}

  poke :: Ptr (TypeID' version) -> TypeID' version -> IO ()
  poke :: Ptr (TypeID' version) -> TypeID' version -> IO ()
poke Ptr (TypeID' version)
ptr (TypeID' Text
prefix UUID
uuid) = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr Ptr (TypeID' version)
ptr) UUID
uuid
    let encodedPrefix :: [Word8]
encodedPrefix = [Word8] -> [Word8]
concat5BitInts forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Num a => a -> a -> a
subtract Word8
96) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
BS.unpack
                      forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
prefix
    forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff @Word8 Ptr (TypeID' version)
ptr Int
16 (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
length [Word8]
encodedPrefix)
    forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m ()
zipWithM_ (forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr (TypeID' version)
ptr forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Num a => a -> a -> a
+ Int
16)) [Int
1..] [Word8]
encodedPrefix
  {-# INLINE poke #-}

instance Hashable (TypeID' version) where
  hashWithSalt :: Int -> TypeID' version -> Int
  hashWithSalt :: Int -> TypeID' version -> Int
hashWithSalt Int
salt (TypeID' Text
prefix UUID
uuid)
    = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Text
prefix forall a. Hashable a => Int -> a -> Int
`hashWithSalt` UUID
uuid
  {-# INLINE hashWithSalt #-}

-- | Get the prefix, 'UUID', and timestamp of a 'TypeID''.
instance IDType (TypeID' version) where
  getPrefix :: TypeID' version -> Text
  getPrefix :: TypeID' version -> Text
getPrefix (TypeID' Text
prefix UUID
_) = Text
prefix
  {-# INLINE getPrefix #-}

  getUUID :: TypeID' version -> UUID
  getUUID :: TypeID' version -> UUID
getUUID (TypeID' Text
_ UUID
uuid) = UUID
uuid
  {-# INLINE getUUID #-}

  getTime :: TypeID' version -> Word64
  getTime :: TypeID' version -> Word64
getTime = UUID -> Word64
V7.getTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IDType a => a -> UUID
getUUID
  {-# INLINE getTime #-}

-- | Conversion between 'TypeID'' and 'String'/'Text'/'ByteString'.
instance IDConv (TypeID' version) where
  string2ID :: String -> Either TypeIDError (TypeID' version)
  string2ID :: String -> Either TypeIDError (TypeID' version)
string2ID = forall (version :: UUIDVersion).
String -> Either TypeIDError (TypeID' version)
parseString
  {-# INLINE string2ID #-}

  text2ID :: Text -> Either TypeIDError (TypeID' version)
  text2ID :: Text -> Either TypeIDError (TypeID' version)
text2ID = forall (version :: UUIDVersion).
Text -> Either TypeIDError (TypeID' version)
parseText
  {-# INLINE text2ID #-}

  byteString2ID :: ByteString -> Either TypeIDError (TypeID' version)
  byteString2ID :: ByteString -> Either TypeIDError (TypeID' version)
byteString2ID = forall (version :: UUIDVersion).
ByteString -> Either TypeIDError (TypeID' version)
parseByteString
  {-# INLINE byteString2ID #-}

  id2String :: TypeID' version -> String
  id2String :: TypeID' version -> String
id2String = forall (version :: UUIDVersion). TypeID' version -> String
toString
  {-# INLINE id2String #-}

  id2Text :: TypeID' version -> Text
  id2Text :: TypeID' version -> Text
id2Text = forall (version :: UUIDVersion). TypeID' version -> Text
toText
  {-# INLINE id2Text #-}

  id2ByteString :: TypeID' version -> ByteString
  id2ByteString :: TypeID' version -> ByteString
id2ByteString = forall (version :: UUIDVersion). TypeID' version -> ByteString
toByteString
  {-# INLINE id2ByteString #-}

  unsafeString2ID :: String -> TypeID' version
  unsafeString2ID :: String -> TypeID' version
unsafeString2ID = forall (version :: UUIDVersion). String -> TypeID' version
unsafeParseString
  {-# INLINE unsafeString2ID #-}

  unsafeText2ID :: Text -> TypeID' version
  unsafeText2ID :: Text -> TypeID' version
unsafeText2ID = forall (version :: UUIDVersion). Text -> TypeID' version
unsafeParseText
  {-# INLINE unsafeText2ID #-}

  unsafeByteString2ID :: ByteString -> TypeID' version
  unsafeByteString2ID :: ByteString -> TypeID' version
unsafeByteString2ID = forall (version :: UUIDVersion). ByteString -> TypeID' version
unsafeParseByteString
  {-# INLINE unsafeByteString2ID #-}

-- | Generate 'Data.TypeIDs.V7.TypeIDs'.
instance IDGen (TypeID' 'V7) where
  type IDGenPrefix (TypeID' 'V7) = 'Just Text

  type IDGenReq (TypeID' 'V7) a = a

  genID_ :: MonadIO m => Proxy (TypeID' 'V7) -> Text -> m (TypeID' 'V7)
  genID_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V7) -> Text -> m (TypeID' 'V7)
genID_ Proxy (TypeID' 'V7)
_ = forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V7)
genTypeID
  {-# INLINE genID_ #-}

  genID'_ :: MonadIO m => Proxy (TypeID' 'V7) -> Text -> m (TypeID' 'V7)
  genID'_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V7) -> Text -> m (TypeID' 'V7)
genID'_ Proxy (TypeID' 'V7)
_ = forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V7)
genTypeID'
  {-# INLINE genID'_ #-}

  genIDs_ :: MonadIO m
          => Proxy (TypeID' 'V7)
          -> Text
          -> Word16
          -> m [TypeID' 'V7]
  genIDs_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V7) -> Text -> Word16 -> m [TypeID' 'V7]
genIDs_ Proxy (TypeID' 'V7)
_ = forall (m :: * -> *).
MonadIO m =>
Text -> Word16 -> m [TypeID' 'V7]
genTypeIDs
  {-# INLINE genIDs_ #-}

  decorate_ :: Proxy (TypeID' 'V7)
            -> Text
            -> UUID
            -> Either TypeIDError (TypeID' 'V7)
  decorate_ :: Proxy (TypeID' 'V7)
-> Text -> UUID -> Either TypeIDError (TypeID' 'V7)
decorate_ Proxy (TypeID' 'V7)
_ = forall (version :: UUIDVersion).
Text -> UUID -> Either TypeIDError (TypeID' version)
decorateTypeID
  {-# INLINE decorate_ #-}

  checkID_ :: Proxy (TypeID' 'V7) -> TypeID' 'V7 -> Maybe TypeIDError
  checkID_ :: Proxy (TypeID' 'V7) -> TypeID' 'V7 -> Maybe TypeIDError
checkID_ Proxy (TypeID' 'V7)
_ = TypeID' 'V7 -> Maybe TypeIDError
checkTypeID
  {-# INLINE checkID_ #-}

  checkIDWithEnv_ :: MonadIO m
                  => Proxy (TypeID' 'V7)
                  -> TypeID' 'V7
                  -> m (Maybe TypeIDError)
  checkIDWithEnv_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V7) -> TypeID' 'V7 -> m (Maybe TypeIDError)
checkIDWithEnv_ Proxy (TypeID' 'V7)
_ = forall (m :: * -> *).
MonadIO m =>
TypeID' 'V7 -> m (Maybe TypeIDError)
checkTypeIDWithEnv
  {-# INLINE checkIDWithEnv_ #-}

-- | Generate 'TypeID'' ''V1's.
instance IDGen (TypeID' 'V1) where
  type IDGenPrefix (TypeID' 'V1) = 'Just Text

  type IDGenReq (TypeID' 'V1) a = a

  genID_ :: MonadIO m => Proxy (TypeID' 'V1) -> Text -> m (TypeID' 'V1)
  genID_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V1) -> Text -> m (TypeID' 'V1)
genID_ Proxy (TypeID' 'V1)
_ = forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V1)
genTypeIDV1
  {-# INLINE genID_ #-}

  genIDs_ :: MonadIO m
          => Proxy (TypeID' 'V1)
          -> Text
          -> Word16
          -> m [TypeID' 'V1]
  genIDs_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V1) -> Text -> Word16 -> m [TypeID' 'V1]
genIDs_ Proxy (TypeID' 'V1)
_ Text
prefix Word16
n = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
    Maybe TypeIDError
Nothing  -> forall a b. (a -> b) -> [a] -> [b]
map (forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix)
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n) (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UUID
nextUUID)
    Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
  {-# INLINE genIDs_ #-}

  decorate_ :: Proxy (TypeID' 'V1)
            -> Text
            -> UUID
            -> Either TypeIDError (TypeID' 'V1)
  decorate_ :: Proxy (TypeID' 'V1)
-> Text -> UUID -> Either TypeIDError (TypeID' 'V1)
decorate_ Proxy (TypeID' 'V1)
_ = forall (version :: UUIDVersion).
Text -> UUID -> Either TypeIDError (TypeID' version)
decorateTypeID
  {-# INLINE decorate_ #-}

  checkID_ :: Proxy (TypeID' 'V1) -> TypeID' 'V1 -> Maybe TypeIDError
  checkID_ :: Proxy (TypeID' 'V1) -> TypeID' 'V1 -> Maybe TypeIDError
checkID_ Proxy (TypeID' 'V1)
_ = TypeID' 'V1 -> Maybe TypeIDError
checkTypeIDV1
  {-# INLINE checkID_ #-}

-- | Generate 'TypeID'' ''V4's.
instance IDGen (TypeID' 'V4) where
  type IDGenPrefix (TypeID' 'V4) = 'Just Text

  type IDGenReq (TypeID' 'V4) a = a

  genID_ :: MonadIO m => Proxy (TypeID' 'V4) -> Text -> m (TypeID' 'V4)
  genID_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V4) -> Text -> m (TypeID' 'V4)
genID_ Proxy (TypeID' 'V4)
_ = forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
genTypeIDV4
  {-# INLINE genID_ #-}

  genID'_ :: MonadIO m => Proxy (TypeID' 'V4) -> Text -> m (TypeID' 'V4)
  genID'_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V4) -> Text -> m (TypeID' 'V4)
genID'_ Proxy (TypeID' 'V4)
_ = forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
genTypeIDV4'
  {-# INLINE genID'_ #-}

  genIDs_ :: MonadIO m
          => Proxy (TypeID' 'V4)
          -> Text
          -> Word16
          -> m [TypeID' 'V4]
  genIDs_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V4) -> Text -> Word16 -> m [TypeID' 'V4]
genIDs_ Proxy (TypeID' 'V4)
_ Text
prefix Word16
n = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
    Maybe TypeIDError
Nothing  -> forall a b. (a -> b) -> [a] -> [b]
map (forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix)
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n) (forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UUID
V4.nextRandom)
    Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
  {-# INLINE genIDs_ #-}

  decorate_ :: Proxy (TypeID' 'V4)
            -> Text
            -> UUID
            -> Either TypeIDError (TypeID' 'V4)
  decorate_ :: Proxy (TypeID' 'V4)
-> Text -> UUID -> Either TypeIDError (TypeID' 'V4)
decorate_ Proxy (TypeID' 'V4)
_ = forall (version :: UUIDVersion).
Text -> UUID -> Either TypeIDError (TypeID' version)
decorateTypeID
  {-# INLINE decorate_ #-}

  checkID_ :: Proxy (TypeID' 'V4) -> TypeID' 'V4 -> Maybe TypeIDError
  checkID_ :: Proxy (TypeID' 'V4) -> TypeID' 'V4 -> Maybe TypeIDError
checkID_ Proxy (TypeID' 'V4)
_ = TypeID' 'V4 -> Maybe TypeIDError
checkTypeIDV4
  {-# INLINE checkID_ #-}

-- | Generate 'TypeID'' ''V5's.
instance IDGen (TypeID' 'V5) where
  type IDGenPrefix (TypeID' 'V5) = 'Just Text

  type IDGenReq (TypeID' 'V5) r = UUID -> [Word8] -> r

  genID_ :: MonadIO m
         => Proxy (TypeID' 'V5) -> Text -> UUID -> [Word8] -> m (TypeID' 'V5)
  genID_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V5) -> Text -> UUID -> [Word8] -> m (TypeID' 'V5)
genID_ Proxy (TypeID' 'V5)
_ = forall (m :: * -> *).
MonadIO m =>
Text -> UUID -> [Word8] -> m (TypeID' 'V5)
genTypeIDV5
  {-# INLINE genID_ #-}

  genIDs_ :: MonadIO m
          => Proxy (TypeID' 'V5)
          -> Text
          -> UUID
          -> [Word8]
          -> Word16
          -> m [TypeID' 'V5]
  -- Apparently this function is useless...
  genIDs_ :: forall (m :: * -> *).
MonadIO m =>
Proxy (TypeID' 'V5)
-> Text -> UUID -> [Word8] -> Word16 -> m [TypeID' 'V5]
genIDs_ Proxy (TypeID' 'V5)
_ Text
prefix UUID
ns [Word8]
obj Word16
n = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
    Maybe TypeIDError
Nothing  -> forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word16
n)
              forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix forall a b. (a -> b) -> a -> b
$ UUID -> [Word8] -> UUID
V5.generateNamed UUID
ns [Word8]
obj)
    Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
  {-# INLINE genIDs_ #-}

  decorate_ :: Proxy (TypeID' 'V5)
            -> Text
            -> UUID
            -> Either TypeIDError (TypeID' 'V5)
  decorate_ :: Proxy (TypeID' 'V5)
-> Text -> UUID -> Either TypeIDError (TypeID' 'V5)
decorate_ Proxy (TypeID' 'V5)
_ = forall (version :: UUIDVersion).
Text -> UUID -> Either TypeIDError (TypeID' version)
decorateTypeID
  {-# INLINE decorate_ #-}

  checkID_ :: Proxy (TypeID' 'V5) -> TypeID' 'V5 -> Maybe TypeIDError
  checkID_ :: Proxy (TypeID' 'V5) -> TypeID' 'V5 -> Maybe TypeIDError
checkID_ Proxy (TypeID' 'V5)
_ = TypeID' 'V5 -> Maybe TypeIDError
checkTypeIDV5
  {-# INLINE checkID_ #-}

-- | Generate a new 'Data.TypeID.V7.TypeID' from a prefix.
--
-- It throws a 'TypeIDError' if the prefix does not match the specification,
-- namely if it's longer than 63 characters or if it contains characters other
-- than lowercase latin letters.
genTypeID :: MonadIO m => Text -> m (TypeID' 'V7)
genTypeID :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V7)
genTypeID = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (m :: * -> *).
MonadIO m =>
Text -> Word16 -> m [TypeID' 'V7]
`genTypeIDs` Word16
1)
{-# INLINE genTypeID #-}

-- | Generate a new 'Data.TypeID.V7.TypeID' from a prefix based on stateless
-- 'UUID'v7.
--
-- See the documentation of 'V7.genUUID'' for more information.
genTypeID' :: MonadIO m => Text -> m (TypeID' 'V7)
genTypeID' :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V7)
genTypeID' Text
prefix = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
  Maybe TypeIDError
Nothing  -> forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V7)
unsafeGenTypeID' Text
prefix
  Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
{-# INLINE genTypeID' #-}

-- | Generate a list of 'Data.TypeID.V7.TypeID's from a prefix.
--
-- It tries its best to generate 'Data.TypeID.V7.TypeID's at the same timestamp,
-- but it may not be possible if we are asking too many 'UUID's at the same
-- time.
--
-- It is guaranteed that the first 32768 'Data.TypeID.V7.TypeID's are generated
-- at the same timestamp.
genTypeIDs :: MonadIO m => Text -> Word16 -> m [TypeID' 'V7]
genTypeIDs :: forall (m :: * -> *).
MonadIO m =>
Text -> Word16 -> m [TypeID' 'V7]
genTypeIDs Text
prefix Word16
n = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
  Maybe TypeIDError
Nothing  -> forall (m :: * -> *).
MonadIO m =>
Text -> Word16 -> m [TypeID' 'V7]
unsafeGenTypeIDs Text
prefix Word16
n
  Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
{-# INLINE genTypeIDs #-}

-- | Generate a new 'TypeID'' ''V1' from a prefix.
--
-- It throws a 'TypeIDError' if the prefix does not match the specification,
-- namely if it's longer than 63 characters or if it contains characters other
-- than lowercase latin letters.
genTypeIDV1 :: MonadIO m => Text -> m (TypeID' 'V1)
genTypeIDV1 :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V1)
genTypeIDV1 Text
prefix = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
  Maybe TypeIDError
Nothing  -> forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V1)
unsafeGenTypeIDV1 Text
prefix
  Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
{-# INLINE genTypeIDV1 #-}

-- | Generate a new 'TypeID'' ''V4' from a prefix.
--
-- It throws a 'TypeIDError' if the prefix does not match the specification,
-- namely if it's longer than 63 characters or if it contains characters other
-- than lowercase latin letters.
genTypeIDV4 :: MonadIO m => Text -> m (TypeID' 'V4)
genTypeIDV4 :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
genTypeIDV4 Text
prefix = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
  Maybe TypeIDError
Nothing  -> forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
unsafeGenTypeIDV4 Text
prefix
  Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
{-# INLINE genTypeIDV4 #-}

-- | Generate a new 'TypeID'' ''V4' from a prefix based on insecure 'UUID'v4.
genTypeIDV4' :: MonadIO m => Text -> m (TypeID' 'V4)
genTypeIDV4' :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
genTypeIDV4' Text
prefix = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
  Maybe TypeIDError
Nothing  -> forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
unsafeGenTypeIDV4' Text
prefix
  Just TypeIDError
err -> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall e a. Exception e => e -> IO a
throwIO TypeIDError
err
{-# INLINE genTypeIDV4' #-}

-- | Generate a new 'TypeID'' ''V5' from a prefix, namespace, and object.
--
-- It throws a 'TypeIDError' if the prefix does not match the specification,
-- namely if it's longer than 63 characters or if it contains characters other
-- than lowercase latin letters.
genTypeIDV5 :: MonadIO m => Text -> UUID -> [Word8] -> m (TypeID' 'V5)
genTypeIDV5 :: forall (m :: * -> *).
MonadIO m =>
Text -> UUID -> [Word8] -> m (TypeID' 'V5)
genTypeIDV5 Text
prefix UUID
ns [Word8]
obj = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
  Maybe TypeIDError
Nothing  -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Text -> UUID -> [Word8] -> TypeID' 'V5
unsafeGenTypeIDV5 Text
prefix UUID
ns [Word8]
obj
  Just TypeIDError
err -> forall a e. Exception e => e -> a
throw TypeIDError
err
{-# INLINE genTypeIDV5 #-}

-- | Obtain a 'TypeID'' from a prefix and a 'UUID'.
decorateTypeID :: Text -> UUID -> Either TypeIDError (TypeID' version)
decorateTypeID :: forall (version :: UUIDVersion).
Text -> UUID -> Either TypeIDError (TypeID' version)
decorateTypeID Text
prefix UUID
uuid = case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
  Maybe TypeIDError
Nothing  -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix UUID
uuid
  Just TypeIDError
err -> forall a b. a -> Either a b
Left TypeIDError
err
{-# INLINE decorateTypeID #-}

-- | Pretty-print a 'TypeID''. It is 'id2String' with concrete type.
toString :: TypeID' version -> String
toString :: forall (version :: UUIDVersion). TypeID' version -> String
toString (TypeID' Text
prefix (UUID Word64
w1 Word64
w2)) = if Text -> Bool
T.null Text
prefix
  then ByteString -> String
suffixEncode ByteString
bs
  else Text -> String
T.unpack Text
prefix forall a. [a] -> [a] -> [a]
++ String
"_" forall a. [a] -> [a] -> [a]
++ ByteString -> String
suffixEncode ByteString
bs
  where
    bs :: ByteString
bs = Put -> ByteString
runPut forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Word64 -> Put
putWord64be [Word64
w1, Word64
w2]
{-# INLINE toString #-}

-- | Pretty-print a 'TypeID'' to strict 'Text'. It is 'id2Text' with concrete
-- type.
toText :: TypeID' version -> Text
toText :: forall (version :: UUIDVersion). TypeID' version -> Text
toText (TypeID' Text
prefix (UUID Word64
w1 Word64
w2)) = if Text -> Bool
T.null Text
prefix
  then String -> Text
T.pack (ByteString -> String
suffixEncode ByteString
bs)
  else Text
prefix forall a. Semigroup a => a -> a -> a
<> Text
"_" forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (ByteString -> String
suffixEncode ByteString
bs)
  where
    bs :: ByteString
bs = Put -> ByteString
runPut forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Word64 -> Put
putWord64be [Word64
w1, Word64
w2]
{-# INLINE toText #-}

-- | Pretty-print a 'TypeID'' to lazy 'ByteString'. It is 'id2ByteString' with
-- concrete type.
toByteString :: TypeID' version -> ByteString
toByteString :: forall (version :: UUIDVersion). TypeID' version -> ByteString
toByteString = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (version :: UUIDVersion). TypeID' version -> String
toString
{-# INLINE toByteString #-}

-- | Parse a 'TypeID'' from its 'String' representation. It is 'string2ID' with
-- concrete type.
parseString :: String -> Either TypeIDError (TypeID' version)
parseString :: forall (version :: UUIDVersion).
String -> Either TypeIDError (TypeID' version)
parseString String
str = case forall (version :: UUIDVersion).
String -> Either TypeIDError (TypeID' version, String)
parseStringS String
str of
  Left TypeIDError
err        -> forall a b. a -> Either a b
Left TypeIDError
err
  Right (TypeID' version
tid, String
"") -> forall a b. b -> Either a b
Right TypeID' version
tid
  Either TypeIDError (TypeID' version, String)
_               -> forall a b. a -> Either a b
Left TypeIDError
TypeIDErrorUUIDError
{-# INLINE parseString #-}

parseStringS :: String -> Either TypeIDError (TypeID' version, String)
parseStringS :: forall (version :: UUIDVersion).
String -> Either TypeIDError (TypeID' version, String)
parseStringS String
str = case forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Char
'_') String
str of
  (String
"", String
_)              -> forall a b. a -> Either a b
Left TypeIDError
TypeIDExtraSeparator
  (String
_, String
"")              -> do
    let (String
uuid, String
rem) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
26 String
str
        bs :: ByteString
bs          = forall a. IsString a => String -> a
fromString String
uuid
    (, String
rem) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
"" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either TypeIDError UUID
decodeUUID ByteString
bs
  (String
prefix, Char
_ : String
suffix) -> do
    let prefix' :: Text
prefix'     = String -> Text
T.pack String
prefix
        (String
uuid, String
rem) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
26 String
suffix
        bs :: ByteString
bs          = forall a. IsString a => String -> a
fromString String
uuid
    case Text -> Maybe TypeIDError
checkPrefix Text
prefix' of
      Maybe TypeIDError
Nothing  -> (, String
rem) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either TypeIDError UUID
decodeUUID ByteString
bs
      Just TypeIDError
err -> forall a b. a -> Either a b
Left TypeIDError
err

-- | Parse a 'TypeID'' from its string representation as a strict 'Text'. It is
-- 'text2ID' with concrete type.
parseText :: Text -> Either TypeIDError (TypeID' version)
parseText :: forall (version :: UUIDVersion).
Text -> Either TypeIDError (TypeID' version)
parseText Text
text = case forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second Text -> Maybe (Char, Text)
T.uncons forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> (Text, Text)
T.span (forall a. Eq a => a -> a -> Bool
/= Char
'_') Text
text of
  (Text
"", Maybe (Char, Text)
_)                    -> forall a b. a -> Either a b
Left TypeIDError
TypeIDExtraSeparator
  (Text
_, Maybe (Char, Text)
Nothing)               -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
""
                            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either TypeIDError UUID
decodeUUID (ByteString -> ByteString
BSL.fromStrict forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
text)
  (Text
prefix, Just (Char
_, Text
suffix)) -> do
    case Text -> Maybe TypeIDError
checkPrefix Text
prefix of
      Maybe TypeIDError
Nothing  -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either TypeIDError UUID
decodeUUID (ByteString -> ByteString
BSL.fromStrict forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
suffix)
      Just TypeIDError
err -> forall a b. a -> Either a b
Left TypeIDError
err

-- | Parse a 'TypeID'' from its string representation as a lazy 'ByteString'. It
-- is 'byteString2ID' with concrete type.
parseByteString :: ByteString -> Either TypeIDError (TypeID' version)
parseByteString :: forall (version :: UUIDVersion).
ByteString -> Either TypeIDError (TypeID' version)
parseByteString ByteString
bs = case forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ByteString -> Maybe (Word8, ByteString)
BSL.uncons forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
BSL.span (forall a. Eq a => a -> a -> Bool
/= Word8
95) ByteString
bs of
  (ByteString
"", Maybe (Word8, ByteString)
_)                    -> forall a b. a -> Either a b
Left TypeIDError
TypeIDExtraSeparator
  (ByteString
_, Maybe (Word8, ByteString)
Nothing)               -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
"" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either TypeIDError UUID
decodeUUID ByteString
bs
  (ByteString
prefix, Just (Word8
_, ByteString
suffix)) -> do
    let prefix' :: Text
prefix' = ByteString -> Text
decodeUtf8 forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BSL.toStrict ByteString
prefix
    case Text -> Maybe TypeIDError
checkPrefix Text
prefix' of
      Maybe TypeIDError
Nothing  -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either TypeIDError UUID
decodeUUID ByteString
suffix
      Just TypeIDError
err -> forall a b. a -> Either a b
Left TypeIDError
err

-- | Parse a 'TypeID'' from its 'String' representation, throwing an error when
-- the parsing fails. It is 'string2IDM' with concrete type.
parseStringM :: MonadIO m => String -> m (TypeID' version)
parseStringM :: forall (m :: * -> *) (version :: UUIDVersion).
MonadIO m =>
String -> m (TypeID' version)
parseStringM = forall a (m :: * -> *). (IDConv a, MonadIO m) => String -> m a
string2IDM
{-# INLINE parseStringM #-}

-- | Parse a 'TypeID'' from its string representation as a strict 'Text',
-- throwing an error when the parsing fails. It is 'text2IDM' with concrete
-- type.
parseTextM :: MonadIO m => Text -> m (TypeID' version)
parseTextM :: forall (m :: * -> *) (version :: UUIDVersion).
MonadIO m =>
Text -> m (TypeID' version)
parseTextM = forall a (m :: * -> *). (IDConv a, MonadIO m) => Text -> m a
text2IDM
{-# INLINE parseTextM #-}

-- | Parse a 'TypeID'' from its string representation as a lazy 'ByteString',
-- throwing an error when the parsing fails. It is 'byteString2IDM' with
-- concrete type.
parseByteStringM :: MonadIO m => ByteString -> m (TypeID' version)
parseByteStringM :: forall (m :: * -> *) (version :: UUIDVersion).
MonadIO m =>
ByteString -> m (TypeID' version)
parseByteStringM = forall a (m :: * -> *). (IDConv a, MonadIO m) => ByteString -> m a
byteString2IDM
{-# INLINE parseByteStringM #-}

-- | Check if the given prefix is a valid 'TypeID'' prefix.
checkPrefix :: Text -> Maybe TypeIDError
checkPrefix :: Text -> Maybe TypeIDError
checkPrefix Text
prefix
  | Text -> Int
T.length Text
prefix forall a. Ord a => a -> a -> Bool
> Int
63 = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Int -> TypeIDError
TypeIDErrorPrefixTooLong (Text -> Int
T.length Text
prefix)
  | Bool
otherwise
      = case Text -> Maybe (Char, Text)
T.uncons ((Char -> Bool) -> Text -> Text
T.dropWhile (forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 Bool -> Bool -> Bool
(&&) Char -> Bool
isLower Char -> Bool
isAscii) Text
prefix) of
        Maybe (Char, Text)
Nothing     -> forall a. Maybe a
Nothing
        Just (Char
c, Text
_) -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Char -> TypeIDError
TypeIDErrorPrefixInvalidChar Char
c
{-# INLINE checkPrefix #-}

-- | Check if the prefix is valid and the suffix 'UUID' has the correct v7
-- version and variant.
checkTypeID :: TypeID' 'V7 -> Maybe TypeIDError
checkTypeID :: TypeID' 'V7 -> Maybe TypeIDError
checkTypeID (TypeID' Text
prefix UUID
uuid)
  = forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ Text -> Maybe TypeIDError
checkPrefix Text
prefix
         , TypeIDError
TypeIDErrorUUIDError forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ UUID -> Bool
V7.validate UUID
uuid) ]
{-# INLINE checkTypeID #-}

-- | Check if the prefix is valid and the suffix 'UUID' has the correct v1
-- version and variant.
checkTypeIDV1 :: TypeID' 'V1 -> Maybe TypeIDError
checkTypeIDV1 :: TypeID' 'V1 -> Maybe TypeIDError
checkTypeIDV1 (TypeID' Text
prefix UUID
uuid)
  = forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ Text -> Maybe TypeIDError
checkPrefix Text
prefix
         , TypeIDError
TypeIDErrorUUIDError forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ UUID -> UUIDVersion -> Bool
validateWithVersion UUID
uuid UUIDVersion
V1) ]
{-# INLINE checkTypeIDV1 #-}

-- | Check if the prefix is valid and the suffix 'UUID' has the correct v4
-- version and variant.
checkTypeIDV4 :: TypeID' 'V4 -> Maybe TypeIDError
checkTypeIDV4 :: TypeID' 'V4 -> Maybe TypeIDError
checkTypeIDV4 (TypeID' Text
prefix UUID
uuid)
  = forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ Text -> Maybe TypeIDError
checkPrefix Text
prefix
         , TypeIDError
TypeIDErrorUUIDError forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ UUID -> UUIDVersion -> Bool
validateWithVersion UUID
uuid UUIDVersion
V4) ]
{-# INLINE checkTypeIDV4 #-}

-- | Check if the prefix is valid and the suffix 'UUID' has the correct v4
-- version and variant.
checkTypeIDV5 :: TypeID' 'V5 -> Maybe TypeIDError
checkTypeIDV5 :: TypeID' 'V5 -> Maybe TypeIDError
checkTypeIDV5 (TypeID' Text
prefix UUID
uuid)
  = forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, MonadPlus m) =>
t (m a) -> m a
msum [ Text -> Maybe TypeIDError
checkPrefix Text
prefix
         , TypeIDError
TypeIDErrorUUIDError forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ UUID -> UUIDVersion -> Bool
validateWithVersion UUID
uuid UUIDVersion
V5) ]
{-# INLINE checkTypeIDV5 #-}

-- | Similar to 'checkTypeID', but also checks if the suffix 'UUID' is
-- generated in the past.
checkTypeIDWithEnv :: MonadIO m => TypeID' 'V7 -> m (Maybe TypeIDError)
checkTypeIDWithEnv :: forall (m :: * -> *).
MonadIO m =>
TypeID' 'V7 -> m (Maybe TypeIDError)
checkTypeIDWithEnv tid :: TypeID' 'V7
tid@(TypeID' Text
_ UUID
uuid)
  = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TypeID' 'V7 -> Maybe TypeIDError
checkTypeID TypeID' 'V7
tid forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`)
         ((TypeIDError
TypeIDErrorUUIDError forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadIO m => UUID -> m Bool
V7.validateWithTime UUID
uuid)
{-# INLINE checkTypeIDWithEnv #-}

-- | Generate a new 'Data.TypeID.V7.TypeID' from a prefix, but without checking
-- if the prefix is valid.
unsafeGenTypeID :: MonadIO m => Text -> m (TypeID' 'V7)
unsafeGenTypeID :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V7)
unsafeGenTypeID = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (m :: * -> *).
MonadIO m =>
Text -> Word16 -> m [TypeID' 'V7]
`unsafeGenTypeIDs` Word16
1)
{-# INLINE unsafeGenTypeID #-}

-- | Generate a new 'TypeID'' ''V1' from a prefix, but without checking if the
-- prefix is valid.
unsafeGenTypeIDV1 :: MonadIO m => Text -> m (TypeID' 'V1)
unsafeGenTypeIDV1 :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V1)
unsafeGenTypeIDV1 Text
prefix = forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UUID
nextUUID
{-# INLINE unsafeGenTypeIDV1 #-}

-- | Generate a new 'TypeID'' ''V4' from a prefix, but without checking if the
-- prefix is valid.
unsafeGenTypeIDV4 :: MonadIO m => Text -> m (TypeID' 'V4)
unsafeGenTypeIDV4 :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
unsafeGenTypeIDV4 Text
prefix = forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO UUID
V4.nextRandom
{-# INLINE unsafeGenTypeIDV4 #-}

-- | Generate a new 'TypeID'' ''V5' from a prefix, namespace, and object, but
-- without checking if the prefix is valid.
unsafeGenTypeIDV5 :: Text -> UUID -> [Word8] -> TypeID' 'V5
unsafeGenTypeIDV5 :: Text -> UUID -> [Word8] -> TypeID' 'V5
unsafeGenTypeIDV5 Text
prefix UUID
ns [Word8]
obj = forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix (UUID -> [Word8] -> UUID
V5.generateNamed UUID
ns [Word8]
obj)
{-# INLINE unsafeGenTypeIDV5 #-}

-- | Generate a new 'Data.TypeID.V7.TypeID' from a prefix based on stateless
-- 'UUID'v7, but without checking if the prefix is valid.
unsafeGenTypeID' :: MonadIO m => Text -> m (TypeID' V7)
unsafeGenTypeID' :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V7)
unsafeGenTypeID' Text
prefix = forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadIO m => m UUID
V7.genUUID'
{-# INLINE unsafeGenTypeID' #-}

-- | Generate a new 'TypeID'' ''V4' from a prefix based on insecure 'UUID'v4,
-- but without checking if the prefix is valid.
unsafeGenTypeIDV4' :: MonadIO m => Text -> m (TypeID' V4)
unsafeGenTypeIDV4' :: forall (m :: * -> *). MonadIO m => Text -> m (TypeID' 'V4)
unsafeGenTypeIDV4' Text
prefix = forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a (m :: * -> *). (Random a, MonadIO m) => m a
randomIO
{-# INLINE unsafeGenTypeIDV4' #-}

-- | Generate n 'Data.TypeID.V7.TypeID's from a prefix, but without checking if
-- the prefix is valid.
--
-- It tries its best to generate 'Data.TypeID.V7.TypeID's at the same timestamp,
-- but it may not be possible if we are asking too many 'UUID's at the same
-- time.
--
-- It is guaranteed that the first 32768 'Data.TypeID.V7.TypeID's are generated
-- at the same timestamp.
unsafeGenTypeIDs :: MonadIO m => Text -> Word16 -> m [TypeID' V7]
unsafeGenTypeIDs :: forall (m :: * -> *).
MonadIO m =>
Text -> Word16 -> m [TypeID' 'V7]
unsafeGenTypeIDs Text
prefix Word16
n = forall a b. (a -> b) -> [a] -> [b]
map (forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadIO m => Word16 -> m [UUID]
V7.genUUIDs Word16
n
{-# INLINE unsafeGenTypeIDs #-}

-- | Parse a 'TypeID'' from its 'String' representation, but crashes when
-- parsing fails.
unsafeParseString :: String -> TypeID' version
unsafeParseString :: forall (version :: UUIDVersion). String -> TypeID' version
unsafeParseString String
str = case forall a. (a -> Bool) -> [a] -> ([a], [a])
span (forall a. Eq a => a -> a -> Bool
/= Char
'_') String
str of
  (String
_, String
"")              -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> UUID
unsafeDecodeUUID forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
str
  (String
prefix, Char
_ : String
suffix) -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' (String -> Text
T.pack String
prefix)
                        forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> UUID
unsafeDecodeUUID forall a b. (a -> b) -> a -> b
$ forall a. IsString a => String -> a
fromString String
suffix
{-# INLINE unsafeParseString #-}

-- | Parse a 'TypeID'' from its string representation as a strict 'Text', but
-- crashes when parsing fails.
unsafeParseText :: Text -> TypeID' version
unsafeParseText :: forall (version :: UUIDVersion). Text -> TypeID' version
unsafeParseText Text
text = case forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second Text -> Maybe (Char, Text)
T.uncons forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> (Text, Text)
T.span (forall a. Eq a => a -> a -> Bool
/= Char
'_') Text
text of
  (Text
_, Maybe (Char, Text)
Nothing)               -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> UUID
unsafeDecodeUUID
                              forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BSL.fromStrict forall a b. (a -> b) -> a -> b
$ Text -> ByteString
encodeUtf8 Text
text
  (Text
prefix, Just (Char
_, Text
suffix)) -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
prefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> UUID
unsafeDecodeUUID
                              forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
BSL.fromStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 forall a b. (a -> b) -> a -> b
$ Text
suffix
{-# INLINE unsafeParseText #-}

-- | Parse a 'TypeID'' from its string representation as a lazy 'ByteString',
-- but crashes when parsing fails.
unsafeParseByteString :: ByteString -> TypeID' version
unsafeParseByteString :: forall (version :: UUIDVersion). ByteString -> TypeID' version
unsafeParseByteString ByteString
bs = case forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second ByteString -> Maybe (Word8, ByteString)
BSL.uncons forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
BSL.span (forall a. Eq a => a -> a -> Bool
/= Word8
95) ByteString
bs of
  (ByteString
_, Maybe (Word8, ByteString)
Nothing)               -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' Text
"" forall a b. (a -> b) -> a -> b
$ ByteString -> UUID
unsafeDecodeUUID ByteString
bs
  (ByteString
prefix, Just (Word8
_, ByteString
suffix)) -> forall (version :: UUIDVersion). Text -> UUID -> TypeID' version
TypeID' (ByteString -> Text
decodeUtf8 forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
BSL.toStrict ByteString
prefix)
                              forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> UUID
unsafeDecodeUUID forall a b. (a -> b) -> a -> b
$ ByteString
suffix
{-# INLINE unsafeParseByteString #-}

concat5BitInts :: [Word8] -> [Word8]
concat5BitInts :: [Word8] -> [Word8]
concat5BitInts
  = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {t} {a}. (Integral t, Num a, Bits t) => t -> [a]
toBytes
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\(Integer
acc :: Integer) Word8
w -> Integer
acc forall a. Bits a => a -> Int -> a
`shiftL` Int
5 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w) Integer
0
  where
    toBytes :: t -> [a]
toBytes t
0 = []
    toBytes t
x = forall a b. (Integral a, Num b) => a -> b
fromIntegral (t
x forall a. Bits a => a -> a -> a
.&. t
0xFF) forall a. a -> [a] -> [a]
: t -> [a]
toBytes (t
x forall a. Bits a => a -> Int -> a
`shiftR` Int
8)
{-# INLINE concat5BitInts #-}

separate5BitInts :: [Word8] -> [Word8]
separate5BitInts :: [Word8] -> [Word8]
separate5BitInts
  = forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {t} {a}. (Integral t, Num a, Bits t) => t -> [a]
toBytes
  forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\(Integer
acc :: Integer) Word8
w -> Integer
acc forall a. Bits a => a -> Int -> a
`shiftL` Int
8 forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w) Integer
0
  where
    toBytes :: t -> [a]
toBytes t
0 = []
    toBytes t
x = forall a b. (Integral a, Num b) => a -> b
fromIntegral (t
x forall a. Bits a => a -> a -> a
.&. t
0x1F) forall a. a -> [a] -> [a]
: t -> [a]
toBytes (t
x forall a. Bits a => a -> Int -> a
`shiftR` Int
5)
{-# INLINE separate5BitInts #-}

-- | A helper for generating 'UUID'v1.
nextUUID :: IO UUID
nextUUID :: IO UUID
nextUUID = IO (Maybe UUID)
V1.nextUUID forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO UUID
nextUUID forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE nextUUID #-}

-- The helpers below are verbatim translations from the official highly magical
-- Go implementation.

suffixEncode :: ByteString -> String
suffixEncode :: ByteString -> String
suffixEncode ByteString
bs = (Array Word8 Char
alphabet forall i e. Ix i => Array i e -> i -> e
!) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. (forall s. ST s a) -> a
runST do
  STUArray s Int Word8
dest <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
0, Int
25) :: ST s (STUArray s Int Word8)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
0 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
0 forall a. Bits a => a -> a -> a
.&. Word8
224) forall a. Bits a => a -> Int -> a
`shiftR` Int
5
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
1 forall a b. (a -> b) -> a -> b
$ ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
0 forall a. Bits a => a -> a -> a
.&. Word8
31
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
2 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
1 forall a. Bits a => a -> a -> a
.&. Word8
248) forall a. Bits a => a -> Int -> a
`shiftR` Int
3
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
3 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
1 forall a. Bits a => a -> a -> a
.&. Word8
7) forall a. Bits a => a -> Int -> a
`shiftL` Int
2) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
2 forall a. Bits a => a -> a -> a
.&. Word8
192) forall a. Bits a => a -> Int -> a
`shiftR` Int
6)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
4 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
2 forall a. Bits a => a -> a -> a
.&. Word8
62) forall a. Bits a => a -> Int -> a
`shiftR` Int
1
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
5 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
2 forall a. Bits a => a -> a -> a
.&. Word8
1) forall a. Bits a => a -> Int -> a
`shiftL` Int
4) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
3 forall a. Bits a => a -> a -> a
.&. Word8
240) forall a. Bits a => a -> Int -> a
`shiftR` Int
4)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
6 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
3 forall a. Bits a => a -> a -> a
.&. Word8
15) forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
4 forall a. Bits a => a -> a -> a
.&. Word8
128) forall a. Bits a => a -> Int -> a
`shiftR` Int
7)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
7 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
4 forall a. Bits a => a -> a -> a
.&. Word8
124) forall a. Bits a => a -> Int -> a
`shiftR` Int
2
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
8 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
4 forall a. Bits a => a -> a -> a
.&. Word8
3) forall a. Bits a => a -> Int -> a
`shiftL` Int
3) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
5 forall a. Bits a => a -> a -> a
.&. Word8
224) forall a. Bits a => a -> Int -> a
`shiftR` Int
5)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
9 forall a b. (a -> b) -> a -> b
$ ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
5 forall a. Bits a => a -> a -> a
.&. Word8
31
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
10 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
6 forall a. Bits a => a -> a -> a
.&. Word8
248) forall a. Bits a => a -> Int -> a
`shiftR` Int
3
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
11 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
6 forall a. Bits a => a -> a -> a
.&. Word8
7) forall a. Bits a => a -> Int -> a
`shiftL` Int
2) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
7 forall a. Bits a => a -> a -> a
.&. Word8
192) forall a. Bits a => a -> Int -> a
`shiftR` Int
6)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
12 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
7 forall a. Bits a => a -> a -> a
.&. Word8
62) forall a. Bits a => a -> Int -> a
`shiftR` Int
1
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
13 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
7 forall a. Bits a => a -> a -> a
.&. Word8
1) forall a. Bits a => a -> Int -> a
`shiftL` Int
4) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
8 forall a. Bits a => a -> a -> a
.&. Word8
240) forall a. Bits a => a -> Int -> a
`shiftR` Int
4)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
14 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
8 forall a. Bits a => a -> a -> a
.&. Word8
15) forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
9 forall a. Bits a => a -> a -> a
.&. Word8
128) forall a. Bits a => a -> Int -> a
`shiftR` Int
7)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
15 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
9 forall a. Bits a => a -> a -> a
.&. Word8
124) forall a. Bits a => a -> Int -> a
`shiftR` Int
2
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
16 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
9 forall a. Bits a => a -> a -> a
.&. Word8
3) forall a. Bits a => a -> Int -> a
`shiftL` Int
3) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
10 forall a. Bits a => a -> a -> a
.&. Word8
224) forall a. Bits a => a -> Int -> a
`shiftR` Int
5)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
17 forall a b. (a -> b) -> a -> b
$ ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
10 forall a. Bits a => a -> a -> a
.&. Word8
31
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
18 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
11 forall a. Bits a => a -> a -> a
.&. Word8
248) forall a. Bits a => a -> Int -> a
`shiftR` Int
3
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
19 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
11 forall a. Bits a => a -> a -> a
.&. Word8
7) forall a. Bits a => a -> Int -> a
`shiftL` Int
2) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
12 forall a. Bits a => a -> a -> a
.&. Word8
192) forall a. Bits a => a -> Int -> a
`shiftR` Int
6)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
20 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
12 forall a. Bits a => a -> a -> a
.&. Word8
62) forall a. Bits a => a -> Int -> a
`shiftR` Int
1
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
21 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
12 forall a. Bits a => a -> a -> a
.&. Word8
1) forall a. Bits a => a -> Int -> a
`shiftL` Int
4) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
13 forall a. Bits a => a -> a -> a
.&. Word8
240) forall a. Bits a => a -> Int -> a
`shiftR` Int
4)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
22 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
13 forall a. Bits a => a -> a -> a
.&. Word8
15) forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
14 forall a. Bits a => a -> a -> a
.&. Word8
128) forall a. Bits a => a -> Int -> a
`shiftR` Int
7)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
23 forall a b. (a -> b) -> a -> b
$ (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
14 forall a. Bits a => a -> a -> a
.&. Word8
124) forall a. Bits a => a -> Int -> a
`shiftR` Int
2
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
24 forall a b. (a -> b) -> a -> b
$ ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
14 forall a. Bits a => a -> a -> a
.&. Word8
3) forall a. Bits a => a -> Int -> a
`shiftL` Int
3) forall a. Bits a => a -> a -> a
.|. ((ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
15 forall a. Bits a => a -> a -> a
.&. Word8
224) forall a. Bits a => a -> Int -> a
`shiftR` Int
5)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
25 forall a b. (a -> b) -> a -> b
$ ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
15 forall a. Bits a => a -> a -> a
.&. Word8
31
  forall i e. Array i e -> [e]
elems forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
unsafeFreeze STUArray s Int Word8
dest
  where
    alphabet :: Array Word8 Char
alphabet = forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Word8
0, Word8
31) String
"0123456789abcdefghjkmnpqrstvwxyz"

suffixDecode :: ByteString -> ByteString
suffixDecode :: ByteString -> ByteString
suffixDecode ByteString
bs = [Word8] -> ByteString
BSL.pack forall a b. (a -> b) -> a -> b
$ forall a. (forall s. ST s a) -> a
runST do
  STUArray s Int Word8
dest <- forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ (Int
0, Int
15) :: ST s (STUArray s Int Word8)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
0 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
0)) forall a. Bits a => a -> Int -> a
`shiftL` Int
5) forall a. Bits a => a -> a -> a
.|. (Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
1))
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
1 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
2)) forall a. Bits a => a -> Int -> a
`shiftL` Int
3) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
3)) forall a. Bits a => a -> Int -> a
`shiftR` Int
2)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
2 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
3)) forall a. Bits a => a -> Int -> a
`shiftL` Int
6) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
4)) forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
5)) forall a. Bits a => a -> Int -> a
`shiftR` Int
4)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
3 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
5)) forall a. Bits a => a -> Int -> a
`shiftL` Int
4) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
6)) forall a. Bits a => a -> Int -> a
`shiftR` Int
1)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
4 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
6)) forall a. Bits a => a -> Int -> a
`shiftL` Int
7) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
7)) forall a. Bits a => a -> Int -> a
`shiftL` Int
2) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
8)) forall a. Bits a => a -> Int -> a
`shiftR` Int
3)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
5 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
8)) forall a. Bits a => a -> Int -> a
`shiftL` Int
5) forall a. Bits a => a -> a -> a
.|. (Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
9))
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
6 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
10)) forall a. Bits a => a -> Int -> a
`shiftL` Int
3) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
11)) forall a. Bits a => a -> Int -> a
`shiftR` Int
2)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
7 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
11)) forall a. Bits a => a -> Int -> a
`shiftL` Int
6) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
12)) forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
13)) forall a. Bits a => a -> Int -> a
`shiftR` Int
4)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
8 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
13)) forall a. Bits a => a -> Int -> a
`shiftL` Int
4) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
14)) forall a. Bits a => a -> Int -> a
`shiftR` Int
1)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
9 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
14)) forall a. Bits a => a -> Int -> a
`shiftL` Int
7) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
15)) forall a. Bits a => a -> Int -> a
`shiftL` Int
2) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
16)) forall a. Bits a => a -> Int -> a
`shiftR` Int
3)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
10 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
16)) forall a. Bits a => a -> Int -> a
`shiftL` Int
5) forall a. Bits a => a -> a -> a
.|. (Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
17))
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
11 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
18)) forall a. Bits a => a -> Int -> a
`shiftL` Int
3) forall a. Bits a => a -> a -> a
.|. (Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
19)) forall a. Bits a => a -> Int -> a
`shiftR` Int
2
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
12 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
19)) forall a. Bits a => a -> Int -> a
`shiftL` Int
6) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
20)) forall a. Bits a => a -> Int -> a
`shiftL` Int
1) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
21)) forall a. Bits a => a -> Int -> a
`shiftR` Int
4)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
13 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
21)) forall a. Bits a => a -> Int -> a
`shiftL` Int
4) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
22)) forall a. Bits a => a -> Int -> a
`shiftR` Int
1)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
14 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
22)) forall a. Bits a => a -> Int -> a
`shiftL` Int
7) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
23)) forall a. Bits a => a -> Int -> a
`shiftL` Int
2) forall a. Bits a => a -> a -> a
.|. ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
24)) forall a. Bits a => a -> Int -> a
`shiftR` Int
3)
  forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Word8
dest Int
15 forall a b. (a -> b) -> a -> b
$ ((Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
24)) forall a. Bits a => a -> Int -> a
`shiftL` Int
5) forall a. Bits a => a -> a -> a
.|. (Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
! (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
25))
  forall i e. Array i e -> [e]
elems forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall i (a :: * -> * -> *) e (m :: * -> *) (b :: * -> * -> *).
(Ix i, MArray a e m, IArray b e) =>
a i e -> m (b i e)
unsafeFreeze STUArray s Int Word8
dest

decodeUUID :: ByteString -> Either TypeIDError UUID
decodeUUID :: ByteString -> Either TypeIDError UUID
decodeUUID ByteString
bs = do
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString -> Int64
BSL.length ByteString
bs forall a. Eq a => a -> a -> Bool
== Int64
26) forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left TypeIDError
TypeIDErrorUUIDError
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString
bs HasCallStack => ByteString -> Int64 -> Word8
`BSL.index` Int64
0 forall a. Ord a => a -> a -> Bool
<= Word8
55) forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left TypeIDError
TypeIDErrorUUIDError
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((forall a. Eq a => a -> a -> Bool
== Word8
0xFF) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Array Word8 Word8
base32Table forall i e. Ix i => Array i e -> i -> e
!)) forall a b. (a -> b) -> a -> b
$ ByteString -> [Word8]
BSL.unpack ByteString
bs) forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left TypeIDError
TypeIDErrorUUIDError
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ByteString -> UUID
unsafeDecodeUUID ByteString
bs
{-# INLINE decodeUUID #-}

unsafeDecodeUUID :: ByteString -> UUID
unsafeDecodeUUID :: ByteString -> UUID
unsafeDecodeUUID
  = forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Word64 -> Word64 -> UUID
UUID forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Get a -> ByteString -> a
runGet (forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 (,)) Get Word64
getWord64be) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
suffixDecode
{-# INLINE unsafeDecodeUUID #-}

base32Table :: Array Word8 Word8
base32Table :: Array Word8 Word8
base32Table = forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Word8
0, Word8
255)
  [ Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0x00, Word8
0x01
  , Word8
0x02, Word8
0x03, Word8
0x04, Word8
0x05, Word8
0x06, Word8
0x07, Word8
0x08, Word8
0x09, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0x0A, Word8
0x0B, Word8
0x0C
  , Word8
0x0D, Word8
0x0E, Word8
0x0F, Word8
0x10, Word8
0x11, Word8
0xFF, Word8
0x12, Word8
0x13, Word8
0xFF, Word8
0x14
  , Word8
0x15, Word8
0xFF, Word8
0x16, Word8
0x17, Word8
0x18, Word8
0x19, Word8
0x1A, Word8
0xFF, Word8
0x1B, Word8
0x1C
  , Word8
0x1D, Word8
0x1E, Word8
0x1F, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF
  , Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF, Word8
0xFF ]