snowchecked-0.0.2.0: A checksummed variation on Twitter's Snowflake UID generation algorithm
LicenseApache 2.0
Maintainersmokejumperit@gmail.com
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Snowchecked

Description

This generates unique (guaranteed) identifiers build from a timestamp, counter, and node id. Identifiers are convertible to values which are monotonically increasing with respect to time.

Synopsis

Documentation

newSnowcheckedGen :: MonadIO io => SnowcheckedConfig -> Word256 -> io SnowcheckedGen Source #

Create a new generator. Takes a configuration and node id. The node id may be any value that fits in a Word256, but it will be truncated to the number of bits specified in the provided configuration.

nextFlake :: MonadIO io => SnowcheckedGen -> io Flake Source #

Generates the next id.

data SnowcheckedConfig Source #

Configuration that specifies how many bits are used for each part of the id. These values are not validated and may be any legal value for the type.

The default value provided by def is 64 bits in total length, just like the original Snowflake algorithm.

Note that specifying 0 check bits results in the normal Snowflake generation. Setting confTimeBits or confCountBits near zero will significantly limit the total number of UIDs that can be generated, as well as the throughput of the UID generation.

Constructors

SnowcheckedConfig 

Fields

Instances

Instances details
Generic SnowcheckedConfig Source # 
Instance details

Defined in Data.Snowchecked.Types

Associated Types

type Rep SnowcheckedConfig :: Type -> Type #

Show SnowcheckedConfig Source # 
Instance details

Defined in Data.Snowchecked.Types

Default SnowcheckedConfig Source # 
Instance details

Defined in Data.Snowchecked.Types

NFData SnowcheckedConfig Source # 
Instance details

Defined in Data.Snowchecked.Types

Methods

rnf :: SnowcheckedConfig -> () #

Eq SnowcheckedConfig Source # 
Instance details

Defined in Data.Snowchecked.Types

Ord SnowcheckedConfig Source # 
Instance details

Defined in Data.Snowchecked.Types

type Rep SnowcheckedConfig Source # 
Instance details

Defined in Data.Snowchecked.Types

type Rep SnowcheckedConfig = D1 ('MetaData "SnowcheckedConfig" "Data.Snowchecked.Types" "snowchecked-0.0.2.0-JwkIfxT25kc6AQyhojYiCd" 'False) (C1 ('MetaCons "SnowcheckedConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "confTimeBits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "confCountBits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)) :*: (S1 ('MetaSel ('Just "confNodeBits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Just "confCheckBits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8))))

data SnowcheckedGen Source #

The state that needs to be communicated between flake generation calls. This should be treated as opaque by consumers of this library: messing about with its internals may cause your code to hang indefinitely.

data Flake Source #

The state of a given generated instance. Note that the actual value is calculated on demand.

Instances

Instances details
Generic Flake Source # 
Instance details

Defined in Data.Snowchecked.Types

Associated Types

type Rep Flake :: Type -> Type #

Methods

from :: Flake -> Rep Flake x #

to :: Rep Flake x -> Flake #

Show Flake Source # 
Instance details

Defined in Data.Snowchecked.Types

Methods

showsPrec :: Int -> Flake -> ShowS #

show :: Flake -> String #

showList :: [Flake] -> ShowS #

NFData Flake Source # 
Instance details

Defined in Data.Snowchecked.Types

Methods

rnf :: Flake -> () #

Eq Flake Source # 
Instance details

Defined in Data.Snowchecked.Types

Methods

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

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

Ord Flake Source # 
Instance details

Defined in Data.Snowchecked.Types

Methods

compare :: Flake -> Flake -> Ordering #

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

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

(>) :: Flake -> Flake -> Bool #

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

max :: Flake -> Flake -> Flake #

min :: Flake -> Flake -> Flake #

type Rep Flake Source # 
Instance details

Defined in Data.Snowchecked.Types

type Rep Flake = D1 ('MetaData "Flake" "Data.Snowchecked.Types" "snowchecked-0.0.2.0-JwkIfxT25kc6AQyhojYiCd" 'False) (C1 ('MetaCons "Flake" 'PrefixI 'True) ((S1 ('MetaSel ('Just "flakeTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word256) :*: S1 ('MetaSel ('Just "flakeCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word256)) :*: (S1 ('MetaSel ('Just "flakeNodeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word256) :*: S1 ('MetaSel ('Just "flakeConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SnowcheckedConfig))))

snowcheckedConfigBitCount :: SnowcheckedConfig -> Word32 Source #

Calculates the number of bits in each Flake generated using a given configuration. It returns a Word32 because there are 4 fields and the bitlength of each field fits in a Word8, so the total bit count must fit within a Word32.

uniqueFlakeCount :: SnowcheckedConfig -> Integer Source #

Provides the count of total number of unique flakes possibly generated by a node using this configuration.