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

Data.UUID.V7

Description

UUIDv7 implementation.

UUIDv7 is not currently present in the uuid package, therefore I have to make a quick patch of my own.

Note that since the specification for v7 is not yet finalised, this module's implementation may change in the future according to the potential adjustments in the specification.

Synopsis

Data type

data UUID #

Type representing Universally Unique Identifiers (UUID) as specified in RFC 4122.

Instances

Instances details
Data UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID #

toConstr :: UUID -> Constr #

dataTypeOf :: UUID -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID #

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

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

gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

Storable UUID

This Storable instance uses the memory layout as described in RFC 4122, but in contrast to the Binary instance, the fields are stored in host byte order.

Instance details

Defined in Data.UUID.Types.Internal

Methods

sizeOf :: UUID -> Int #

alignment :: UUID -> Int #

peekElemOff :: Ptr UUID -> Int -> IO UUID #

pokeElemOff :: Ptr UUID -> Int -> UUID -> IO () #

peekByteOff :: Ptr b -> Int -> IO UUID #

pokeByteOff :: Ptr b -> Int -> UUID -> IO () #

peek :: Ptr UUID -> IO UUID #

poke :: Ptr UUID -> UUID -> IO () #

Read UUID 
Instance details

Defined in Data.UUID.Types.Internal

Show UUID

Pretty prints a UUID (without quotation marks). See also toString.

>>> show nil
"00000000-0000-0000-0000-000000000000"
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Binary UUID

This Binary instance is compatible with RFC 4122, storing the fields in network order as 16 bytes.

Instance details

Defined in Data.UUID.Types.Internal

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf :: UUID -> () #

Eq UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

Ord UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

compare :: UUID -> UUID -> Ordering #

(<) :: UUID -> UUID -> Bool #

(<=) :: UUID -> UUID -> Bool #

(>) :: UUID -> UUID -> Bool #

(>=) :: UUID -> UUID -> Bool #

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Hashable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

Random UUID

This Random instance produces insecure version 4 UUIDs as specified in RFC 4122.

Instance details

Defined in Data.UUID.Types.Internal

Methods

randomR :: RandomGen g => (UUID, UUID) -> g -> (UUID, g) #

random :: RandomGen g => g -> (UUID, g) #

randomRs :: RandomGen g => (UUID, UUID) -> g -> [UUID] #

randoms :: RandomGen g => g -> [UUID] #

Uniform UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

uniformM :: StatefulGen g m => g -> m UUID #

FromJSON UUID 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UUID 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON UUID 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UUID 
Instance details

Defined in Data.Aeson.Types.ToJSON

Lift UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

lift :: Quote m => UUID -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => UUID -> Code m UUID #

UUIDv7 generation

genUUID :: MonadIO m => m UUID Source #

Generate a UUIDv7.

genUUID' :: MonadIO m => m UUID Source #

Generate a stateless UUIDv7.

It is faster than genUUID but it is not guaranteed to be monotonically increasing if multiple UUIDs are generated at the same timestamp.

In use cases where the ordering is not important, this function is could be preferred.

genUUIDs :: MonadIO m => Word16 -> m [UUID] Source #

Generate a list of UUIDv7s.

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

Validation

validate :: UUID -> Bool Source #

Validate the version and variant of the UUIDv7.

validateWithTime :: MonadIO m => UUID -> m Bool Source #

Validate the version and variant of the UUIDv7 as well as its timestamp is no greater than the current time.

Miscellaneous helpers

getTime :: UUID -> Word64 Source #

Get the time field (unix_ts_ms) of a UUIDv7.

getEpochMilli :: MonadIO m => m Word64 Source #

Get the current time in milliseconds since the Unix epoch.