ron-0.2: RON, RON-RDT, and RON-Schema

Safe HaskellNone
LanguageHaskell2010

RON.UUID

Contents

Synopsis

Documentation

data UUID Source #

Universally unique identifier of anything

Constructors

UUID !Word64 !Word64 
Instances
Eq UUID Source # 
Instance details

Defined in RON.UUID

Methods

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

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

Data UUID Source # 
Instance details

Defined in RON.UUID

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 :: (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 #

Ord UUID Source # 
Instance details

Defined in RON.UUID

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 #

Show UUID Source #

RON-Text-encoding

Instance details

Defined in RON.UUID

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Generic UUID Source # 
Instance details

Defined in RON.UUID

Associated Types

type Rep UUID :: Type -> Type #

Methods

from :: UUID -> Rep UUID x #

to :: Rep UUID x -> UUID #

Hashable UUID Source # 
Instance details

Defined in RON.UUID

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

NFData UUID Source # 
Instance details

Defined in RON.UUID

Methods

rnf :: UUID -> () #

ReplicatedAsPayload UUID Source # 
Instance details

Defined in RON.Data.Internal

Replicated UUID Source # 
Instance details

Defined in RON.Data.Internal

type Rep UUID Source # 
Instance details

Defined in RON.UUID

data UuidFields Source #

UUID split in parts

Instances
Eq UuidFields Source # 
Instance details

Defined in RON.UUID

Show UuidFields Source # 
Instance details

Defined in RON.UUID

build :: UuidFields -> UUID Source #

Build UUID from parts

buildX :: Word4 -> Word60 -> Word64 Source #

Build former 64 bits of UUID from parts

buildY :: Word2 -> Word2 -> Word60 -> Word64 Source #

Build latter 64 bits of UUID from parts

split :: UUID -> UuidFields Source #

Split UUID into parts

succValue :: UUID -> UUID Source #

Increment field uuidValue of a UUID

zero :: UUID Source #

UUID with all zero fields

pattern Zero :: UUID Source #

UUID with all zero fields

Name

getName Source #

Arguments

:: UUID 
-> Maybe (ByteString, ByteString)

(scope, name) for a scoped name; (name, "") for a global name

Convert UUID to a name

mkName Source #

Arguments

:: Monad m 
=> ByteString

name, max 10 Base64 letters

-> m UUID 

Make an unscoped (unqualified) name

mkScopedName Source #

Arguments

:: Monad m 
=> ByteString

scope, max 10 Base64 letters

-> ByteString

local name, max 10 Base64 letters

-> m UUID 

Make a scoped (qualified) name

Base32 encoding, suitable for file names

decodeBase32 :: FilePath -> Maybe UUID Source #

Decode a UUID from a Base32 string

encodeBase32 :: UUID -> FilePath Source #

Encode a UUID to a Base32 string