License | MIT |
---|---|
Maintainer | mmzk1526@outlook.com |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An implementation of the TypeID specification: https://github.com/jetpack-io/typeid.
It is a re-export of Data.TypeID.V7.
Synopsis
- type TypeID = TypeID' 'V7
- data TypeID' (version :: UUIDVersion)
- getPrefix :: IDType a => a -> Text
- getUUID :: IDType a => a -> UUID
- getTime :: IDType a => a -> Word64
- genTypeID :: MonadIO m => Text -> m TypeID
- genTypeID' :: MonadIO m => Text -> m TypeID
- genTypeIDs :: MonadIO m => Text -> Word16 -> m [TypeID]
- decorateTypeID :: Text -> UUID -> Either TypeIDError TypeID
- genID :: forall a m. (IDGen a, MonadIO m) => GenFunc (IDGenPrefix a) (IDGenReq a (m a))
- genID' :: forall a m. (IDGen a, MonadIO m) => GenFunc (IDGenPrefix a) (IDGenReq a (m a))
- genIDs :: forall a m. (IDGen a, MonadIO m) => GenFunc (IDGenPrefix a) (IDGenReq a (Word16 -> m [a]))
- decorate :: forall a. IDGen a => GenFunc (IDGenPrefix a) (UUID -> ResWithErr (IDGenPrefix a) a)
- checkPrefix :: Text -> Maybe TypeIDError
- checkTypeID :: TypeID -> Maybe TypeIDError
- checkTypeIDWithEnv :: MonadIO m => TypeID -> m (Maybe TypeIDError)
- checkID :: forall a. IDGen a => a -> Maybe TypeIDError
- checkIDWithEnv :: forall a m. (IDGen a, MonadIO m) => a -> m (Maybe TypeIDError)
- toString :: TypeID -> String
- toText :: TypeID -> Text
- toByteString :: TypeID -> ByteString
- parseString :: String -> Either TypeIDError TypeID
- parseText :: Text -> Either TypeIDError TypeID
- parseByteString :: ByteString -> Either TypeIDError TypeID
- parseStringM :: MonadIO m => String -> m TypeID
- parseTextM :: MonadIO m => Text -> m TypeID
- parseByteStringM :: MonadIO m => ByteString -> m TypeID
- id2String :: IDConv a => a -> String
- id2Text :: IDConv a => a -> Text
- id2ByteString :: IDConv a => a -> ByteString
- string2ID :: IDConv a => String -> Either TypeIDError a
- text2ID :: IDConv a => Text -> Either TypeIDError a
- byteString2ID :: IDConv a => ByteString -> Either TypeIDError a
- string2IDM :: (IDConv a, MonadIO m) => String -> m a
- text2IDM :: (IDConv a, MonadIO m) => Text -> m a
- byteString2IDM :: (IDConv a, MonadIO m) => ByteString -> m a
Data types
data TypeID' (version :: UUIDVersion) Source #
This data type also supports TypeID
s with UUID
versions
other than v7.
The constructor is not exposed to the public API to prevent generating
invalid TypeID'
s.
Instances
getTime :: IDType a => a -> Word64 Source #
Get the timestamp of the identifier. Returns 0 if the identifier is not timestamp-based.
TypeID
generation (TypeID
-specific)
genTypeID :: MonadIO m => Text -> m TypeID Source #
Generate a new 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.
decorateTypeID :: Text -> UUID -> Either TypeIDError TypeID Source #
TypeID
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.
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 (TypeID
-specific)
checkPrefix :: Text -> Maybe TypeIDError Source #
Check if the given prefix is a valid TypeID
prefix.
checkTypeID :: TypeID -> Maybe TypeIDError Source #
Check if the prefix is valid and the suffix UUID
has the correct v7
version and variant.
checkTypeIDWithEnv :: MonadIO m => TypeID -> m (Maybe TypeIDError) Source #
Similar to checkTypeID
, 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 (TypeID
-specific)
toByteString :: TypeID -> ByteString Source #
Pretty-print a TypeID
to lazy ByteString
. It is id2ByteString
with
concrete type.
parseString :: String -> Either TypeIDError TypeID Source #
parseByteString :: ByteString -> Either TypeIDError TypeID Source #
Parse a TypeID
from its string representation as a lazy ByteString
. It
is byteString2ID
with concrete type.
parseStringM :: MonadIO m => String -> m TypeID Source #
Parse a TypeID
from its String
representation, throwing an error when
the parsing fails. It is string2IDM
with concrete type.
parseByteStringM :: MonadIO m => ByteString -> m TypeID Source #
Parse a TypeID
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)
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.