Safe Haskell | None |
---|---|
Language | Haskell2010 |
This library implements the Universally Unique Lexicographically Sortable Identifier, as described at https://github.com/alizain/ulid.
UUID can be suboptimal for many uses-cases because:
- It isn't the most character efficient way of encoding 128 bits of randomness
- UUID v1/v2 is impractical in many environments, as it requires access to a unique, stable MAC address
- UUID v3/v5 requires a unique seed and produces randomly distributed IDs, which can cause fragmentation in many data structures
- UUID v4 provides no other information than randomness, which can cause fragmentation in many data structures
Instead, herein is proposed ULID:
- 128-bit compatibility with UUID
- 1.21e+24 unique ULIDs per millisecond
- Lexicographically sortable!
- Canonically encoded as a 26 character text, as opposed to the 36 character UUID
- Uses Douglas Crockford's base32 for better efficiency and readability (5 bits per character)
- Case insensitive
- No special characters (URL safe)
Synopsis
- data ULID = ULID {
- timeStamp :: !ULIDTimeStamp
- random :: !ULIDRandom
- getULIDTime :: POSIXTime -> IO ULID
- getULID :: IO ULID
- ulidToInteger :: ULID -> Integer
- ulidFromInteger :: Integer -> Either Text ULID
Documentation
t <- getULIDTimeStamp r <- getULIDRandom pure $ ULID t r
ULID | |
|
Instances
Eq ULID Source # | |
Data ULID Source # | |
Defined in Data.ULID gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ULID -> c ULID # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ULID # dataTypeOf :: ULID -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ULID) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ULID) # gmapT :: (forall b. Data b => b -> b) -> ULID -> ULID # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r # gmapQ :: (forall d. Data d => d -> u) -> ULID -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ULID -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ULID -> m ULID # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ULID -> m ULID # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ULID -> m ULID # | |
Ord ULID Source # | |
Read ULID Source # | |
Show ULID Source # | |
Generic ULID Source # | |
Binary ULID Source # | |
NFData ULID Source # | Because of the strictness annotations, this shouldn't be needed and shouldn't do anything. This is tested and confirmed in the benchmark, but since the work to put it here has already been done it's no harm to leave it in. |
Hashable ULID Source # | |
Random ULID Source # | |
type Rep ULID Source # | |
Defined in Data.ULID type Rep ULID = D1 ('MetaData "ULID" "Data.ULID" "ulid-0.3.2.0-BcOZlFVsiMK2FGyhpAn5jU" 'False) (C1 ('MetaCons "ULID" 'PrefixI 'True) (S1 ('MetaSel ('Just "timeStamp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ULIDTimeStamp) :*: S1 ('MetaSel ('Just "random") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ULIDRandom))) |
Derive a ULID using a specified time and default random number generator
ulidToInteger :: ULID -> Integer Source #
Convert a ULID to its corresponding (at most) 128-bit Integer.
Integer equivalents retain sortable trait (same sort order).
This could be useful for storing in a database using a smaller field
than storing the shown Text
,
but still human-readable unlike the Binary version.