| License | MIT | 
|---|---|
| Maintainer | mmzk1526@outlook.com | 
| Portability | GHC | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.TypeID.V4
Synopsis
- type TypeIDV4 = TypeID' 'V4
- getPrefix :: IDType a => a -> Text
- getUUID :: IDType a => a -> UUID
- genTypeID :: MonadIO m => Text -> m TypeIDV4
- genTypeID' :: MonadIO m => Text -> m TypeIDV4
- decorateTypeID :: Text -> UUID -> Either TypeIDError TypeIDV4
- 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))
- decorate :: forall a. IDGen a => GenFunc (IDGenPrefix a) (UUID -> ResWithErr (IDGenPrefix a) a)
- checkPrefix :: Text -> Maybe TypeIDError
- checkTypeID :: TypeIDV4 -> Maybe TypeIDError
- checkID :: forall a. IDGen a => a -> Maybe TypeIDError
- toString :: TypeIDV4 -> String
- toText :: TypeIDV4 -> Text
- toByteString :: TypeIDV4 -> ByteString
- parseString :: String -> Either TypeIDError TypeIDV4
- parseText :: Text -> Either TypeIDError TypeIDV4
- parseByteString :: ByteString -> Either TypeIDError TypeIDV4
- parseStringM :: MonadIO m => String -> m TypeIDV4
- parseTextM :: MonadIO m => Text -> m TypeIDV4
- parseByteStringM :: MonadIO m => ByteString -> m TypeIDV4
- 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
TypeIDV4 generation (TypeIDV4-specific)
genTypeID :: MonadIO m => Text -> m TypeIDV4 Source #
Generate a new TypeIDV4 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 TypeIDV4 Source #
TypeIDV4 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 (TypeIDV4-specific)
checkPrefix :: Text -> Maybe TypeIDError Source #
Check if the given prefix is a valid TypeIDV4 prefix.
checkTypeID :: TypeIDV4 -> Maybe TypeIDError Source #
Check if the prefix is valid and the suffix UUID has the correct v4
 version and variant.
Validation (class methods)
checkID :: forall a. IDGen a => a -> Maybe TypeIDError Source #
Check the validity of the identifier.
Encoding & decoding (TypeIDV4-specific)
toByteString :: TypeIDV4 -> ByteString Source #
Pretty-print a TypeIDV4 to lazy ByteString. It is id2ByteString
 with concrete type.
parseByteString :: ByteString -> Either TypeIDError TypeIDV4 Source #
Parse a TypeIDV4 from its string representation as a lazy ByteString.
 It is byteString2ID with concrete type.
parseStringM :: MonadIO m => String -> m TypeIDV4 Source #
Parse a TypeIDV4 from its String representation, throwing an error when
 the parsing fails. It is string2IDM with concrete type.
parseByteStringM :: MonadIO m => ByteString -> m TypeIDV4 Source #
Parse a TypeIDV4 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.