{- |
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)
-}

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Data.ULID (
    ULID(..),
    getULIDTime,
    getULID,
    ulidToInteger,
    ulidFromInteger
) where

import           Control.DeepSeq
import           Data.Binary
import qualified Data.ByteString.Lazy  as LBS
import           Data.Data
import           Data.Hashable
import           Data.Monoid           ((<>))
import           Data.Text as T
import           Data.Time.Clock.POSIX
import           GHC.Generics
import           System.IO.Unsafe
import qualified System.Random         as R

import           Data.Binary.Roll
import           Data.ULID.Random
import           Data.ULID.TimeStamp


{- |
> t <- getULIDTimeStamp
> r <- getULIDRandom
> pure $ ULID t r
-}
data ULID = ULID
  { ULID -> ULIDTimeStamp
timeStamp :: !ULIDTimeStamp
  , ULID -> ULIDRandom
random    :: !ULIDRandom
  }
  deriving (ULID -> ULID -> Bool
(ULID -> ULID -> Bool) -> (ULID -> ULID -> Bool) -> Eq ULID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ULID -> ULID -> Bool
$c/= :: ULID -> ULID -> Bool
== :: ULID -> ULID -> Bool
$c== :: ULID -> ULID -> Bool
Eq, Typeable, Typeable ULID
DataType
Constr
Typeable ULID
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> ULID -> c ULID)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c ULID)
-> (ULID -> Constr)
-> (ULID -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c ULID))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ULID))
-> ((forall b. Data b => b -> b) -> ULID -> ULID)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r)
-> (forall u. (forall d. Data d => d -> u) -> ULID -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> ULID -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> ULID -> m ULID)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ULID -> m ULID)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> ULID -> m ULID)
-> Data ULID
ULID -> DataType
ULID -> Constr
(forall b. Data b => b -> b) -> ULID -> ULID
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ULID -> c ULID
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ULID
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ULID -> u
forall u. (forall d. Data d => d -> u) -> ULID -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ULID -> m ULID
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ULID -> m ULID
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ULID
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ULID -> c ULID
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ULID)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ULID)
$cULID :: Constr
$tULID :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> ULID -> m ULID
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ULID -> m ULID
gmapMp :: (forall d. Data d => d -> m d) -> ULID -> m ULID
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ULID -> m ULID
gmapM :: (forall d. Data d => d -> m d) -> ULID -> m ULID
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ULID -> m ULID
gmapQi :: Int -> (forall d. Data d => d -> u) -> ULID -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ULID -> u
gmapQ :: (forall d. Data d => d -> u) -> ULID -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ULID -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ULID -> r
gmapT :: (forall b. Data b => b -> b) -> ULID -> ULID
$cgmapT :: (forall b. Data b => b -> b) -> ULID -> ULID
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ULID)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ULID)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c ULID)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ULID)
dataTypeOf :: ULID -> DataType
$cdataTypeOf :: ULID -> DataType
toConstr :: ULID -> Constr
$ctoConstr :: ULID -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ULID
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ULID
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ULID -> c ULID
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ULID -> c ULID
$cp1Data :: Typeable ULID
Data, (forall x. ULID -> Rep ULID x)
-> (forall x. Rep ULID x -> ULID) -> Generic ULID
forall x. Rep ULID x -> ULID
forall x. ULID -> Rep ULID x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ULID x -> ULID
$cfrom :: forall x. ULID -> Rep ULID x
Generic)

instance Ord ULID where
    compare :: ULID -> ULID -> Ordering
compare (ULID ULIDTimeStamp
ts1 ULIDRandom
_) (ULID ULIDTimeStamp
ts2 ULIDRandom
_) = ULIDTimeStamp -> ULIDTimeStamp -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ULIDTimeStamp
ts1 ULIDTimeStamp
ts2

instance Show ULID where
    show :: ULID -> String
show (ULID ULIDTimeStamp
ts ULIDRandom
bytes) = ULIDTimeStamp -> String
forall a. Show a => a -> String
show ULIDTimeStamp
ts String -> ShowS
forall a. [a] -> [a] -> [a]
++ ULIDRandom -> String
forall a. Show a => a -> String
show ULIDRandom
bytes

instance Read ULID where
    readsPrec :: Int -> ReadS ULID
readsPrec Int
_ String
str = do
        (ULIDTimeStamp
ts, String
str2) <- ReadS ULIDTimeStamp
forall a. Read a => ReadS a
reads String
str
        (ULIDRandom
rn, String
str3) <- ReadS ULIDRandom
forall a. Read a => ReadS a
reads String
str2
        (ULID, String) -> [(ULID, String)]
forall (m :: * -> *) a. Monad m => a -> m a
return (ULIDTimeStamp -> ULIDRandom -> ULID
ULID ULIDTimeStamp
ts ULIDRandom
rn, String
str3)

instance Binary ULID where
    put :: ULID -> Put
put (ULID ULIDTimeStamp
ts ULIDRandom
bytes) = ULIDTimeStamp -> Put
forall t. Binary t => t -> Put
put ULIDTimeStamp
ts Put -> Put -> Put
forall a. Semigroup a => a -> a -> a
<> ULIDRandom -> Put
forall t. Binary t => t -> Put
put ULIDRandom
bytes
    get :: Get ULID
get = do
        ULIDTimeStamp
ts <- Get ULIDTimeStamp
forall t. Binary t => Get t
get
        ULIDRandom
bytes <- Get ULIDRandom
forall t. Binary t => Get t
get
        ULID -> Get ULID
forall (m :: * -> *) a. Monad m => a -> m a
return (ULID -> Get ULID) -> ULID -> Get ULID
forall a b. (a -> b) -> a -> b
$ ULIDTimeStamp -> ULIDRandom -> ULID
ULID ULIDTimeStamp
ts ULIDRandom
bytes

-- | 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.
instance NFData ULID where
    rnf :: ULID -> ()
rnf (ULID ULIDTimeStamp
ts ULIDRandom
bytes) = ULIDTimeStamp -> ()
forall a. NFData a => a -> ()
rnf ULIDTimeStamp
ts () -> () -> ()
`seq` ULIDRandom -> ()
forall a. NFData a => a -> ()
rnf ULIDRandom
bytes

instance R.Random ULID where
    randomR :: (ULID, ULID) -> g -> (ULID, g)
randomR (ULID, ULID)
_ = g -> (ULID, g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
R.random -- ignore range
    random :: g -> (ULID, g)
random g
g = IO (ULID, g) -> (ULID, g)
forall a. IO a -> a
unsafePerformIO (IO (ULID, g) -> (ULID, g)) -> IO (ULID, g) -> (ULID, g)
forall a b. (a -> b) -> a -> b
$ do
        ULIDTimeStamp
t <- IO ULIDTimeStamp
getULIDTimeStamp
        let (ULIDRandom
r, g
g') = g -> (ULIDRandom, g)
forall g. RandomGen g => g -> (ULIDRandom, g)
mkULIDRandom g
g
        (ULID, g) -> IO (ULID, g)
forall (m :: * -> *) a. Monad m => a -> m a
return (ULIDTimeStamp -> ULIDRandom -> ULID
ULID ULIDTimeStamp
t ULIDRandom
r, g
g')

instance Hashable ULID where
    hashWithSalt :: Int -> ULID -> Int
hashWithSalt Int
salt ULID
ulid = Int -> ByteString -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (ULID -> ByteString
forall a. Binary a => a -> ByteString
encode ULID
ulid)


-- | Derive a ULID using a specified time and default random number generator
getULIDTime
  :: POSIXTime  -- ^ Specified UNIX time with millisecond precision
                --   (e.g. 1469918176.385)
  -> IO ULID
getULIDTime :: POSIXTime -> IO ULID
getULIDTime POSIXTime
t = do
    let t' :: ULIDTimeStamp
t' = POSIXTime -> ULIDTimeStamp
mkULIDTimeStamp POSIXTime
t
    ULIDRandom
r <- IO ULIDRandom
getULIDRandom
    ULID -> IO ULID
forall (m :: * -> *) a. Monad m => a -> m a
return (ULID -> IO ULID) -> ULID -> IO ULID
forall a b. (a -> b) -> a -> b
$ ULIDTimeStamp -> ULIDRandom -> ULID
ULID ULIDTimeStamp
t' ULIDRandom
r


-- | Derive a ULID using the current time and default random number generator
getULID :: IO ULID
getULID :: IO ULID
getULID = do
    ULIDTimeStamp
t <- IO ULIDTimeStamp
getULIDTimeStamp
    ULIDRandom
r <- IO ULIDRandom
getULIDRandom
    ULID -> IO ULID
forall (m :: * -> *) a. Monad m => a -> m a
return (ULID -> IO ULID) -> ULID -> IO ULID
forall a b. (a -> b) -> a -> b
$ ULIDTimeStamp -> ULIDRandom -> ULID
ULID ULIDTimeStamp
t ULIDRandom
r


-- | 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.
ulidToInteger :: ULID -> Integer
ulidToInteger :: ULID -> Integer
ulidToInteger =
    [Word8] -> Integer
roll ([Word8] -> Integer) -> (ULID -> [Word8]) -> ULID -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
LBS.unpack (ByteString -> [Word8]) -> (ULID -> ByteString) -> ULID -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ULID -> ByteString
forall a. Binary a => a -> ByteString
encode


-- | Convert a ULID from its corresponding 128-bit Integer.
ulidFromInteger
  :: Integer -- ^ The ULID's Integer equivalent, as generated by toInteger
  -> Either Text ULID
ulidFromInteger :: Integer -> Either Text ULID
ulidFromInteger Integer
n
    | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = Text -> Either Text ULID
forall a b. a -> Either a b
Left Text
"Value must not be negative"
    | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
maxValidInteger = Text -> Either Text ULID
forall a b. a -> Either a b
Left
        Text
"Value must not be larger than the maximum safe Integer size (128 bits)"
    | Bool
otherwise = ULID -> Either Text ULID
forall a b. b -> Either a b
Right
        (ULID -> Either Text ULID)
-> (Integer -> ULID) -> Integer -> Either Text ULID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ULID
forall a. Binary a => ByteString -> a
decode (ByteString -> ULID) -> (Integer -> ByteString) -> Integer -> ULID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Word8] -> ByteString
LBS.pack ([Word8] -> ByteString)
-> (Integer -> [Word8]) -> Integer -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer -> [Word8]
unroll Int
16 (Integer -> Either Text ULID) -> Integer -> Either Text ULID
forall a b. (a -> b) -> a -> b
$ Integer
n  -- 16 bytes = 128 bit
  where
    maxValidInteger :: Integer
    maxValidInteger :: Integer
maxValidInteger = (Integer
2 Integer -> Integer -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ Integer
128) Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
1