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

Data.KindID.V7

Description

Similar to Data.TypeID, but the type is statically determined in the type level.

Synopsis

Data types

type KindID = KindID' 'V7 Source #

A type alias for the default KindID implementation with UUIDv7.

type KindIDV7 = KindID Source #

A type alias for KindID.

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.

KindID generation (KindID-specific)

genKindID :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix), MonadIO m) => m (KindID prefix) Source #

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

genKindID' :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix), MonadIO m) => m (KindID prefix) Source #

Generate a new KindID from a prefix based on stateless UUIDv7.

See the documentation of genUUID' for more information.

genKindIDs :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix), MonadIO m) => Word16 -> m [KindID prefix] Source #

Generate a list of KindIDs from a prefix.

It tries its best to generate KindIDs at the same timestamp, but it may not be possible if we are asking too many UUIDs at the same time.

It is guaranteed that the first 32768 KindIDs are generated at the same timestamp.

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

Obtain a KindID from a prefix and a UUID.

KindID 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.

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

Similar to genID, but stateless. It can be a faster implementation than genID, but it does not guarantee any stateful property, such as monotonically increasing for UUIDv7-based identifiers.

The default implementation is the same as genID.

genIDs :: forall a m. (IDGen a, MonadIO m) => GenFunc (IDGenPrefix a) (IDGenReq a (Word16 -> m [a])) Source #

Generate a list of identifiers 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 (KindID-specific)

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

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

checkKindIDWithEnv :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix), MonadIO m) => KindID' 'V7 prefix -> m (Maybe TypeIDError) Source #

Similar to checkKindID, but also checks if the suffix UUID is generated in the past.

Validation (class methods)

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

Check the validity of the identifier.

checkIDWithEnv :: forall a m. (IDGen a, MonadIO m) => a -> m (Maybe TypeIDError) Source #

Check the validity of the identifier, potentially with impure criteria.

Encoding & decoding (KindID-specific)

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

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

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

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

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

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

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

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

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

Parse a KindID 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 (KindID prefix) Source #

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

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

Parse a KindID 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 (KindID prefix) Source #

Parse a KindID 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 (KindID prefix) Source #

Parse a KindID 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)) => KindID prefix -> TypeID Source #

Convert a KindID to a TypeID.

fromTypeID :: (ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => TypeID -> Maybe (KindID prefix) Source #

Convert a TypeID to a KindID. Returns Nothing if the prefix does not match.