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

Data.KindID

Description

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

When using TypeID, if we want to check if the type matches, we usually need to get the prefix of the TypeID and compare it with the desired prefix at runtime. However, with Haskell's type system, we can do this at compile time instead. We call this TypeID with compile-time prefix a KindID.

Of course, that would require the desired prefix to be known at compile time. This is actually quite common, especially when we are using one prefix for one table in the database.

For example, suppose we have a function that takes a KindID with the prefix "user", it may have a signature like this: f :: KindID "user" -> IO ()

Then if we try to pass in a KindID with the prefix "post", the compiler will complain, thus removing the runtime check and the associated overhead.

All the prefixes are type-checked at compile time, so if we try to pass in invalid prefixes, the compiler (again) will complain.

This module contains functions to generate and parse these type-level TypeIDs as well as conversion functions to and from the usual term-level TypeIDs. These functions are usually used with a type application, e.g.

do
  tid <- genKindID @"user"
  ...
Synopsis

Data types

data KindID prefix Source #

A TypeID with the prefix encoded at type level.

It is dubbed KindID because we the prefix here is a data kind rather than a type.

Instances

Instances details
(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => Read (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

Methods

readsPrec :: Int -> ReadS (KindID prefix) #

readList :: ReadS [KindID prefix] #

readPrec :: ReadPrec (KindID prefix) #

readListPrec :: ReadPrec [KindID prefix] #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => Show (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

Methods

showsPrec :: Int -> KindID prefix -> ShowS #

show :: KindID prefix -> String #

showList :: [KindID prefix] -> ShowS #

Eq (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

Methods

(==) :: KindID prefix -> KindID prefix -> Bool #

(/=) :: KindID prefix -> KindID prefix -> Bool #

Ord (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

Methods

compare :: KindID prefix -> KindID prefix -> Ordering #

(<) :: KindID prefix -> KindID prefix -> Bool #

(<=) :: KindID prefix -> KindID prefix -> Bool #

(>) :: KindID prefix -> KindID prefix -> Bool #

(>=) :: KindID prefix -> KindID prefix -> Bool #

max :: KindID prefix -> KindID prefix -> KindID prefix #

min :: KindID prefix -> KindID prefix -> KindID prefix #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => Hashable (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

Methods

hashWithSalt :: Int -> KindID prefix -> Int #

hash :: KindID prefix -> Int #

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

Conversion between KindID and StringTextByteString.

Instance details

Defined in Data.KindID.Internal

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

Generate KindIDs.

Instance details

Defined in Data.KindID.Internal

Associated Types

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

Methods

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

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

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

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

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

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

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

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

Instance details

Defined in Data.KindID.Internal

Methods

getPrefix :: KindID prefix -> Text Source #

getUUID :: KindID prefix -> UUID Source #

getTime :: KindID prefix -> Word64 Source #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => FromJSON (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

Methods

parseJSON :: Value -> Parser (KindID prefix) #

parseJSONList :: Value -> Parser [KindID prefix] #

omittedField :: Maybe (KindID prefix) #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => FromJSONKey (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => ToJSON (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

Methods

toJSON :: KindID prefix -> Value #

toEncoding :: KindID prefix -> Encoding #

toJSONList :: [KindID prefix] -> Value #

toEncodingList :: [KindID prefix] -> Encoding #

omitField :: KindID prefix -> Bool #

(ToPrefix prefix, ValidPrefix (PrefixSymbol prefix)) => ToJSONKey (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

type IDGenPrefix (KindID prefix) Source # 
Instance details

Defined in Data.KindID.Internal

type IDGenPrefix (KindID prefix) = 'Nothing :: Maybe Type

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)

nilKindID :: KindID "" Source #

Deprecated: Will be removed in the next major release.

The nil KindID.

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 statelesss 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) (m a) Source #

Generate a new identifier with the given prefix.

genID' :: forall a m. (IDGen a, MonadIO m) => GenFunc (IDGenPrefix 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) (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 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 parseString 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 parseText 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 parseByteString 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.

Type-level & term-level conversion

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

Convert a KindID to a TypeID.

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

Convert a TypeID to a KindID. If the actual prefix does not match with the expected one as defined by the type, it returns Nothing.