License | MIT |
---|---|
Maintainer | mmzk1526@outlook.com |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A module with the APIs for any TypeID
-ish identifier type.
These type classes are useful to define custom TypeID-ish identifier types. For example, if one wishes to remove the constraints on prefix, or use a different UUID version for the suffix.
Synopsis
- type TypeIDLike a = (IDType a, IDConv a, IDGen a)
- class IDType a where
- class IDConv a where
- string2ID :: String -> Either TypeIDError a
- text2ID :: Text -> Either TypeIDError a
- byteString2ID :: ByteString -> Either TypeIDError a
- id2String :: a -> String
- id2Text :: a -> Text
- id2ByteString :: a -> ByteString
- string2IDM :: MonadIO m => String -> m a
- text2IDM :: MonadIO m => Text -> m a
- byteString2IDM :: MonadIO m => ByteString -> m a
- unsafeString2ID :: String -> a
- unsafeText2ID :: Text -> a
- unsafeByteString2ID :: ByteString -> a
- class IDGen a where
- type IDGenPrefix a :: Maybe Type
- type IDGenReq a r :: Type
- genID_ :: MonadIO m => Proxy a -> GenFunc (IDGenPrefix a) (IDGenReq a (m a))
- genID'_ :: forall m. MonadIO m => Proxy a -> GenFunc (IDGenPrefix a) (IDGenReq a (m a))
- genIDs_ :: forall m. MonadIO m => Proxy a -> GenFunc (IDGenPrefix a) (IDGenReq a (Word16 -> m [a]))
- decorate_ :: Proxy a -> GenFunc (IDGenPrefix a) (UUID -> ResWithErr (IDGenPrefix a) a)
- checkID_ :: Proxy a -> a -> Maybe TypeIDError
- checkIDWithEnv_ :: MonadIO m => Proxy a -> a -> m (Maybe TypeIDError)
- decorate :: forall a. IDGen a => GenFunc (IDGenPrefix a) (UUID -> ResWithErr (IDGenPrefix a) a)
- 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]))
- checkID :: forall a. IDGen a => a -> Maybe TypeIDError
- checkIDWithEnv :: forall a m. (IDGen a, MonadIO m) => a -> m (Maybe TypeIDError)
- type family GenFunc prefix res where ...
- type family ResWithErr prefix res where ...
Type classes
type TypeIDLike a = (IDType a, IDConv a, IDGen a) Source #
A constraint synonym for a TypeID
-ish identifier type that
supports ID generation and string conversion.
getPrefix :: a -> Text Source #
Get the prefix of the identifier.
Get the UUID suffix of the identifier.
getTime :: a -> Word64 Source #
Get the timestamp of the identifier. Returns 0 if the identifier is not timestamp-based.
A type class for converting between a TypeID
-ish
identifier type and some string representations.
string2ID, id2String | string2ID, id2Text | string2ID, id2ByteString | text2ID, id2String | text2ID, id2Text | text2ID, id2ByteString | byteString2ID, id2String | byteString2ID, id2Text | byteString2ID, id2ByteString
string2ID :: String -> Either TypeIDError a Source #
Parse the identifier from its String
representation.
text2ID :: Text -> Either TypeIDError a Source #
Parse the identifier from its string representation as a strict Text
.
byteString2ID :: ByteString -> Either TypeIDError a Source #
Parse the identifier from its string representation as a lazy
ByteString
.
id2String :: a -> String Source #
Pretty-print the identifier to a String
.
Pretty-print the identifier to a strict Text
.
id2ByteString :: a -> ByteString Source #
Pretty-print the identifier to a lazy ByteString
.
string2IDM :: MonadIO m => String -> m a Source #
Parse the identifier from its String
representation, throwing an error
when the parsing fails.
text2IDM :: 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 :: MonadIO m => ByteString -> m a Source #
Parse the identifier from its string representation as a lazy
ByteString
, throwing an error when the parsing fails.
unsafeString2ID :: String -> a Source #
Parse the identifier from its String
representation, but crashes when
the parsing fails.
unsafeText2ID :: Text -> a Source #
Parse the identifier from its string representation as a strict Text
,
but crashes when the parsing fails.
unsafeByteString2ID :: ByteString -> a Source #
Parse the identifier from its string representation as a lazy
ByteString
, but crashes when the parsing fails.
Instances
A type class for generating TypeID
-ish identifiers.
The methods in this type class are not directly used since each of them has
a dummy Proxy
in order to compile. We implement the methods here and use
the methods without the underscore suffix instead.
type IDGenPrefix a :: Maybe Type Source #
If the identifier has compile-time determined prefix, this type should be
'Nothing
. Otherwise it should be 'Just prefix
where prefix
is the
type of the prefix (e.g. Text
).
type IDGenReq a r :: Type Source #
If the identifier's generation requires additional information (such as
UUID
version 5), this type corresponds to how to generate r
from the
required information. Otherwise it should be simply
type IDGenReq a r = r
.
genID_ :: MonadIO m => Proxy a -> GenFunc (IDGenPrefix a) (IDGenReq a (m a)) Source #
Generate an identifier with the given prefix.
genID'_ :: forall m. MonadIO m => Proxy a -> 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 UUID
v7-based identifiers.
The default implementation is the same as genID
_.
genIDs_ :: forall m. MonadIO m => Proxy a -> GenFunc (IDGenPrefix a) (IDGenReq a (Word16 -> m [a])) Source #
Generate a list of identifiers with the given prefix.
decorate_ :: Proxy a -> GenFunc (IDGenPrefix a) (UUID -> ResWithErr (IDGenPrefix a) a) Source #
Generate a new identifier with the given prefix and UUID
suffix.
checkID_ :: Proxy a -> a -> Maybe TypeIDError Source #
Check the validity of the identifier.
checkIDWithEnv_ :: MonadIO m => Proxy a -> a -> m (Maybe TypeIDError) Source #
Check the validity of the identifier, potentially with impure criteria.
Instances
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.
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.
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.
Helper types
type family GenFunc prefix res where ... Source #
A function generator based on the IDGenPrefix
type family.
type family ResWithErr prefix res where ... Source #
A result that may contain an error, based on the IDGenPrefix
type family.
In other words, if the prefix type is already encoded in the type level,
we are certain that the prefix is valid, so the result type does not need the
Either TypeIDError
part.
ResWithErr ('Just prefix) res = Either TypeIDError res | |
ResWithErr 'Nothing res = res |