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

Data.TypeID.Class

Description

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

class IDType a where Source #

A type class for a TypeID-ish identifier type, which has a Text prefix and a UUID suffix.

Methods

getPrefix :: a -> Text Source #

Get the prefix of the identifier.

getUUID :: a -> UUID Source #

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.

Instances

Instances details
IDType (TypeID' version) Source #

Get the prefix, UUID, and timestamp of a TypeID'.

Instance details

Defined in Data.TypeID.Internal

Methods

getPrefix :: TypeID' version -> Text Source #

getUUID :: TypeID' version -> UUID Source #

getTime :: TypeID' version -> Word64 Source #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => IDType (KindID' version prefix) Source #

Get the prefix, UUID, and timestamp of a KindID'.

Instance details

Defined in Data.KindID.Internal

Methods

getPrefix :: KindID' version prefix -> Text Source #

getUUID :: KindID' version prefix -> UUID Source #

getTime :: KindID' version prefix -> Word64 Source #

class IDConv a where Source #

A type class for converting between a TypeID-ish identifier type and some string representations.

Methods

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.

id2Text :: a -> Text Source #

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

Instances details
IDConv (TypeID' version) Source #

Conversion between TypeID' and StringTextByteString.

Instance details

Defined in Data.TypeID.Internal

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => IDConv (KindID' version prefix) Source #

Conversion between KindID' and StringTextByteString.

Instance details

Defined in Data.KindID.Internal

Methods

string2ID :: String -> Either TypeIDError (KindID' version prefix) Source #

text2ID :: Text -> Either TypeIDError (KindID' version prefix) Source #

byteString2ID :: ByteString -> Either TypeIDError (KindID' version prefix) Source #

id2String :: KindID' version prefix -> String Source #

id2Text :: KindID' version prefix -> Text Source #

id2ByteString :: KindID' version prefix -> ByteString Source #

string2IDM :: MonadIO m => String -> m (KindID' version prefix) Source #

text2IDM :: MonadIO m => Text -> m (KindID' version prefix) Source #

byteString2IDM :: MonadIO m => ByteString -> m (KindID' version prefix) Source #

unsafeString2ID :: String -> KindID' version prefix Source #

unsafeText2ID :: Text -> KindID' version prefix Source #

unsafeByteString2ID :: ByteString -> KindID' version prefix Source #

class IDGen a where Source #

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.

Minimal complete definition

genID_, genIDs_, decorate_, checkID_

Associated Types

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 .

Methods

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 UUIDv7-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

Instances details
IDGen (TypeID' 'V1) Source #

Generate TypeID' 'V1s.

Instance details

Defined in Data.TypeID.Internal

Associated Types

type IDGenPrefix (TypeID' 'V1) :: Maybe Type Source #

type IDGenReq (TypeID' 'V1) r Source #

IDGen (TypeID' 'V4) Source #

Generate TypeID' 'V4s.

Instance details

Defined in Data.TypeID.Internal

Associated Types

type IDGenPrefix (TypeID' 'V4) :: Maybe Type Source #

type IDGenReq (TypeID' 'V4) r Source #

IDGen (TypeID' 'V5) Source #

Generate TypeID' 'V5s.

Instance details

Defined in Data.TypeID.Internal

Associated Types

type IDGenPrefix (TypeID' 'V5) :: Maybe Type Source #

type IDGenReq (TypeID' 'V5) r Source #

IDGen (TypeID' 'V7) Source #

Generate TypeIDs.

Instance details

Defined in Data.TypeID.Internal

Associated Types

type IDGenPrefix (TypeID' 'V7) :: Maybe Type Source #

type IDGenReq (TypeID' 'V7) r Source #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => IDGen (KindID' 'V1 prefix) Source #

Generate KindID' 'V1s.

Instance details

Defined in Data.KindID.Internal

Associated Types

type IDGenPrefix (KindID' 'V1 prefix) :: Maybe Type Source #

type IDGenReq (KindID' 'V1 prefix) r Source #

Methods

genID_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V1 prefix) -> GenFunc (IDGenPrefix (KindID' 'V1 prefix)) (IDGenReq (KindID' 'V1 prefix) (m (KindID' 'V1 prefix))) Source #

genID'_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V1 prefix) -> GenFunc (IDGenPrefix (KindID' 'V1 prefix)) (IDGenReq (KindID' 'V1 prefix) (m (KindID' 'V1 prefix))) Source #

genIDs_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V1 prefix) -> GenFunc (IDGenPrefix (KindID' 'V1 prefix)) (IDGenReq (KindID' 'V1 prefix) (Word16 -> m [KindID' 'V1 prefix])) Source #

decorate_ :: Proxy (KindID' 'V1 prefix) -> GenFunc (IDGenPrefix (KindID' 'V1 prefix)) (UUID -> ResWithErr (IDGenPrefix (KindID' 'V1 prefix)) (KindID' 'V1 prefix)) Source #

checkID_ :: Proxy (KindID' 'V1 prefix) -> KindID' 'V1 prefix -> Maybe TypeIDError Source #

checkIDWithEnv_ :: MonadIO m => Proxy (KindID' 'V1 prefix) -> KindID' 'V1 prefix -> m (Maybe TypeIDError) Source #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => IDGen (KindID' 'V4 prefix) Source #

Generate KindID' 'V4s.

Instance details

Defined in Data.KindID.Internal

Associated Types

type IDGenPrefix (KindID' 'V4 prefix) :: Maybe Type Source #

type IDGenReq (KindID' 'V4 prefix) r Source #

Methods

genID_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V4 prefix) -> GenFunc (IDGenPrefix (KindID' 'V4 prefix)) (IDGenReq (KindID' 'V4 prefix) (m (KindID' 'V4 prefix))) Source #

genID'_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V4 prefix) -> GenFunc (IDGenPrefix (KindID' 'V4 prefix)) (IDGenReq (KindID' 'V4 prefix) (m (KindID' 'V4 prefix))) Source #

genIDs_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V4 prefix) -> GenFunc (IDGenPrefix (KindID' 'V4 prefix)) (IDGenReq (KindID' 'V4 prefix) (Word16 -> m [KindID' 'V4 prefix])) Source #

decorate_ :: Proxy (KindID' 'V4 prefix) -> GenFunc (IDGenPrefix (KindID' 'V4 prefix)) (UUID -> ResWithErr (IDGenPrefix (KindID' 'V4 prefix)) (KindID' 'V4 prefix)) Source #

checkID_ :: Proxy (KindID' 'V4 prefix) -> KindID' 'V4 prefix -> Maybe TypeIDError Source #

checkIDWithEnv_ :: MonadIO m => Proxy (KindID' 'V4 prefix) -> KindID' 'V4 prefix -> m (Maybe TypeIDError) Source #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => IDGen (KindID' 'V5 prefix) Source #

Generate KindID' 'V5s.

Instance details

Defined in Data.KindID.Internal

Associated Types

type IDGenPrefix (KindID' 'V5 prefix) :: Maybe Type Source #

type IDGenReq (KindID' 'V5 prefix) r Source #

Methods

genID_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V5 prefix) -> GenFunc (IDGenPrefix (KindID' 'V5 prefix)) (IDGenReq (KindID' 'V5 prefix) (m (KindID' 'V5 prefix))) Source #

genID'_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V5 prefix) -> GenFunc (IDGenPrefix (KindID' 'V5 prefix)) (IDGenReq (KindID' 'V5 prefix) (m (KindID' 'V5 prefix))) Source #

genIDs_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V5 prefix) -> GenFunc (IDGenPrefix (KindID' 'V5 prefix)) (IDGenReq (KindID' 'V5 prefix) (Word16 -> m [KindID' 'V5 prefix])) Source #

decorate_ :: Proxy (KindID' 'V5 prefix) -> GenFunc (IDGenPrefix (KindID' 'V5 prefix)) (UUID -> ResWithErr (IDGenPrefix (KindID' 'V5 prefix)) (KindID' 'V5 prefix)) Source #

checkID_ :: Proxy (KindID' 'V5 prefix) -> KindID' 'V5 prefix -> Maybe TypeIDError Source #

checkIDWithEnv_ :: MonadIO m => Proxy (KindID' 'V5 prefix) -> KindID' 'V5 prefix -> m (Maybe TypeIDError) Source #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => IDGen (KindID' 'V7 prefix) Source #

Generate KindIDs.

Instance details

Defined in Data.KindID.Internal

Associated Types

type IDGenPrefix (KindID' 'V7 prefix) :: Maybe Type Source #

type IDGenReq (KindID' 'V7 prefix) r Source #

Methods

genID_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V7 prefix) -> GenFunc (IDGenPrefix (KindID' 'V7 prefix)) (IDGenReq (KindID' 'V7 prefix) (m (KindID' 'V7 prefix))) Source #

genID'_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V7 prefix) -> GenFunc (IDGenPrefix (KindID' 'V7 prefix)) (IDGenReq (KindID' 'V7 prefix) (m (KindID' 'V7 prefix))) Source #

genIDs_ :: forall (m :: Type -> Type). MonadIO m => Proxy (KindID' 'V7 prefix) -> GenFunc (IDGenPrefix (KindID' 'V7 prefix)) (IDGenReq (KindID' 'V7 prefix) (Word16 -> m [KindID' 'V7 prefix])) Source #

decorate_ :: Proxy (KindID' 'V7 prefix) -> GenFunc (IDGenPrefix (KindID' 'V7 prefix)) (UUID -> ResWithErr (IDGenPrefix (KindID' 'V7 prefix)) (KindID' 'V7 prefix)) Source #

checkID_ :: Proxy (KindID' 'V7 prefix) -> KindID' 'V7 prefix -> Maybe TypeIDError Source #

checkIDWithEnv_ :: MonadIO m => Proxy (KindID' 'V7 prefix) -> KindID' 'V7 prefix -> m (Maybe TypeIDError) Source #

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.

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.

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.

Equations

GenFunc ('Just prefix) res = prefix -> res 
GenFunc 'Nothing res = res 

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.

Equations

ResWithErr ('Just prefix) res = Either TypeIDError res 
ResWithErr 'Nothing res = res