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

Data.TypeID

Description

An implementation of the TypeID specification: https://github.com/jetpack-io/typeid.

It is a re-export of Data.TypeID.V7.

Synopsis

Data types

type TypeID = TypeID' 'V7 Source #

A type alias for the default TypeID implementation with UUIDv7.

data TypeID' (version :: UUIDVersion) Source #

This data type also supports TypeIDs with UUID versions other than v7.

The constructor is not exposed to the public API to prevent generating invalid TypeID's.

Instances

Instances details
Typeable version => Data (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeID' version -> c (TypeID' version) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TypeID' version) #

toConstr :: TypeID' version -> Constr #

dataTypeOf :: TypeID' version -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TypeID' version)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TypeID' version)) #

gmapT :: (forall b. Data b => b -> b) -> TypeID' version -> TypeID' version #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeID' version -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeID' version -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypeID' version -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeID' version -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeID' version -> m (TypeID' version) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeID' version -> m (TypeID' version) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeID' version -> m (TypeID' version) #

Storable (TypeID' version) Source #

Similar to the Binary instance, but the UUID is stored in host endian.

Instance details

Defined in Data.TypeID.Internal

Methods

sizeOf :: TypeID' version -> Int #

alignment :: TypeID' version -> Int #

peekElemOff :: Ptr (TypeID' version) -> Int -> IO (TypeID' version) #

pokeElemOff :: Ptr (TypeID' version) -> Int -> TypeID' version -> IO () #

peekByteOff :: Ptr b -> Int -> IO (TypeID' version) #

pokeByteOff :: Ptr b -> Int -> TypeID' version -> IO () #

peek :: Ptr (TypeID' version) -> IO (TypeID' version) #

poke :: Ptr (TypeID' version) -> TypeID' version -> IO () #

Read (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

readsPrec :: Int -> ReadS (TypeID' version) #

readList :: ReadS [TypeID' version] #

readPrec :: ReadPrec (TypeID' version) #

readListPrec :: ReadPrec [TypeID' version] #

Show (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

showsPrec :: Int -> TypeID' version -> ShowS #

show :: TypeID' version -> String #

showList :: [TypeID' version] -> ShowS #

Binary (TypeID' version) Source #

Since the specification does not formulate a concrete binary format, this instance is based on the following custom format:

  • The first 16 bytes are the suffix UUID encoded in base32.
  • The next byte is the length of the prefix encoded in a byte.
  • The next bytes are the prefix, each letter taking 5 bits, mapping 'a' to 1 and 'z' to 26. The underscore '_' is mapped to 27.

Note that the prefix and the UUID is swapped compared to the string representation, this is for the convenience of the use case where only the suffix UUID is required. Because of this, the sorting order may be different from the string representation, but they are guaranteed to be the same if the same prefix is used.

Instance details

Defined in Data.TypeID.Internal

Methods

put :: TypeID' version -> Put #

get :: Get (TypeID' version) #

putList :: [TypeID' version] -> Put #

Eq (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

(==) :: TypeID' version -> TypeID' version -> Bool #

(/=) :: TypeID' version -> TypeID' version -> Bool #

Ord (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

compare :: TypeID' version -> TypeID' version -> Ordering #

(<) :: TypeID' version -> TypeID' version -> Bool #

(<=) :: TypeID' version -> TypeID' version -> Bool #

(>) :: TypeID' version -> TypeID' version -> Bool #

(>=) :: TypeID' version -> TypeID' version -> Bool #

max :: TypeID' version -> TypeID' version -> TypeID' version #

min :: TypeID' version -> TypeID' version -> TypeID' version #

Hashable (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

hashWithSalt :: Int -> TypeID' version -> Int #

hash :: TypeID' version -> Int #

IDConv (TypeID' version) Source #

Conversion between TypeID' and StringTextByteString.

Instance details

Defined in Data.TypeID.Internal

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 #

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 #

FromJSON (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

parseJSON :: Value -> Parser (TypeID' version) #

parseJSONList :: Value -> Parser [TypeID' version] #

omittedField :: Maybe (TypeID' version) #

FromJSONKey (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

ToJSON (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

Methods

toJSON :: TypeID' version -> Value #

toEncoding :: TypeID' version -> Encoding #

toJSONList :: [TypeID' version] -> Value #

toEncodingList :: [TypeID' version] -> Encoding #

omitField :: TypeID' version -> Bool #

ToJSONKey (TypeID' version) Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenPrefix (TypeID' 'V1) Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenPrefix (TypeID' 'V4) Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenPrefix (TypeID' 'V5) Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenPrefix (TypeID' 'V7) Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenReq (TypeID' 'V1) a Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenReq (TypeID' 'V1) a = a
type IDGenReq (TypeID' 'V4) a Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenReq (TypeID' 'V4) a = a
type IDGenReq (TypeID' 'V5) r Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenReq (TypeID' 'V5) r = UUID -> [Word8] -> r
type IDGenReq (TypeID' 'V7) a Source # 
Instance details

Defined in Data.TypeID.Internal

type IDGenReq (TypeID' 'V7) a = a

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.

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.

genTypeID' :: MonadIO m => Text -> m TypeID Source #

Generate a new TypeID from a prefix based on stateless UUIDv7.

See the documentation of genUUID' for more information.

genTypeIDs :: MonadIO m => Text -> Word16 -> m [TypeID] Source #

Generate a list of TypeIDs from a prefix.

It tries its best to generate TypeIDs 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 TypeIDs are generated at the same timestamp.

decorateTypeID :: Text -> UUID -> Either TypeIDError TypeID Source #

Obtain a TypeID from a prefix and a UUID.

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.

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.

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)

toString :: TypeID -> String Source #

Pretty-print a TypeID. It is id2String with concrete type.

toText :: TypeID -> Text Source #

Pretty-print a TypeID to strict Text. It is id2Text with concrete type.

toByteString :: TypeID -> ByteString Source #

Pretty-print a TypeID to lazy ByteString. It is id2ByteString with concrete type.

parseString :: String -> Either TypeIDError TypeID Source #

Parse a TypeID from its String representation. It is string2ID with concrete type.

parseText :: Text -> Either TypeIDError TypeID Source #

Parse a TypeID from its string representation as a strict Text. It is text2ID with concrete type.

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.

parseTextM :: MonadIO m => Text -> m TypeID Source #

Parse a TypeID from its string representation as a strict Text, throwing an error when the parsing fails. It is text2IDM 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)

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.

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.