mmzk-typeid-0.6.0.1: A TypeID implementation for Haskell
LicenseMIT
Maintainermmzk1526@outlook.com
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.KindID.V5

Description

KindID with UUIDv5.

Synopsis

Data types

type KindIDV5 = KindID' 'V5 Source #

Similar to KindID, but uses UUIDv5.

getPrefix :: IDType a => a -> Text Source #

Get the prefix of the identifier.

getUUID :: IDType a => a -> UUID Source #

Get the UUID suffix of the identifier.

getTime :: IDType a => a -> Word64 Source #

Get the timestamp of the identifier. Returns 0 if the identifier is not timestamp-based.

KindIDV5 generation (KindIDV5-specific)

genKindID :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => UUID -> [Word8] -> KindIDV5 prefix Source #

Generate a new KindIDV5 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.

decorateKindID :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => UUID -> KindIDV5 prefix Source #

Obtain a KindIDV5 from a prefix and a UUID.

KindIDV5 generation (class methods)

genID :: forall a m. (IDGen a, MonadIO m) => GenFunc (IDGenPrefix a) (IDGenReq a (m a)) Source #

Generate a new identifier with the given prefix.

decorate :: forall a. IDGen a => GenFunc (IDGenPrefix a) (UUID -> ResWithErr (IDGenPrefix a) a) Source #

Generate a new identifier with the given prefix and UUID suffix.

Validation (KindIDV5-specific)

checkKindID :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => KindIDV5 prefix -> Maybe TypeIDError Source #

Check if the prefix is valid and the suffix UUID has the correct v5 version and variant.

Validation (class methods)

checkID :: forall a. IDGen a => a -> Maybe TypeIDError Source #

Check the validity of the identifier.

Encoding & decoding (KindIDV5-specific)

toString :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => KindIDV5 prefix -> String Source #

Pretty-print a KindIDV5. It is id2String with concrete type.

toText :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => KindIDV5 prefix -> Text Source #

Pretty-print a KindIDV5 to strict Text. It is id2Text with concrete type.

toByteString :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => KindIDV5 prefix -> ByteString Source #

Pretty-print a KindIDV5 to lazy ByteString. It is id2ByteString with concrete type.

parseString :: forall prefix. (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => String -> Either TypeIDError (KindIDV5 prefix) Source #

Parse a KindIDV5 from its String representation. It is string2ID with concrete type.

parseText :: forall prefix. (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => Text -> Either TypeIDError (KindIDV5 prefix) Source #

Parse a KindIDV5 from its string representation as a strict Text. It is text2ID with concrete type.

parseByteString :: forall prefix. (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => ByteString -> Either TypeIDError (KindIDV5 prefix) Source #

Parse a KindIDV5 from its string representation as a lazy ByteString. It is byteString2ID with concrete type.

parseStringM :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix), MonadIO m) => String -> m (KindIDV5 prefix) Source #

Parse a KindIDV5 from its String representation, throwing an error when the parsing fails. It is string2IDM with concrete type.

parseTextM :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix), MonadIO m) => Text -> m (KindIDV5 prefix) Source #

Parse a KindIDV5 from its string representation as a strict Text, throwing an error when the parsing fails. It is text2IDM with concrete type.

parseByteStringM :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix), MonadIO m) => ByteString -> m (KindIDV5 prefix) Source #

Parse a KindIDV5 from its string representation as a lazy ByteString, throwing an error when the parsing fails. It is byteString2IDM with concrete type.

Encoding & decoding (class methods)

id2String :: IDConv a => a -> String Source #

Pretty-print the identifier to a String.

id2Text :: IDConv a => a -> Text Source #

Pretty-print the identifier to a strict Text.

id2ByteString :: IDConv a => a -> ByteString Source #

Pretty-print the identifier to a lazy ByteString.

string2ID :: IDConv a => String -> Either TypeIDError a Source #

Parse the identifier from its String representation.

text2ID :: IDConv a => Text -> Either TypeIDError a Source #

Parse the identifier from its string representation as a strict Text.

byteString2ID :: IDConv a => ByteString -> Either TypeIDError a Source #

Parse the identifier from its string representation as a lazy ByteString.

string2IDM :: (IDConv a, MonadIO m) => String -> m a Source #

Parse the identifier from its String representation, throwing an error when the parsing fails.

text2IDM :: (IDConv a, MonadIO m) => Text -> m a Source #

Parse the identifier from its string representation as a strict Text, throwing an error when the parsing fails.

byteString2IDM :: (IDConv a, MonadIO m) => ByteString -> m a Source #

Parse the identifier from its string representation as a lazy ByteString, throwing an error when the parsing fails.

Type-level & term-level conversion

toTypeID :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => KindIDV5 prefix -> TypeIDV5 Source #

Convert a KindIDV5 to a TypeIDV5.

fromTypeID :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => TypeIDV5 -> Maybe (KindIDV5 prefix) Source #

Convert a TypeIDV5 to a KindIDV5. Returns Nothing if the prefix does not match.