uuid-1.3.13: For creating, comparing, parsing and printing Universally Unique Identifiers

Copyright(c) 20082012 Antoine Latter
LicenseBSD-style
Maintaineraslatter@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.UUID

Description

This library is useful for comparing, parsing and printing Universally Unique Identifiers. See http://en.wikipedia.org/wiki/UUID for the general idea. See http://tools.ietf.org/html/rfc4122 for the specification.

  • Random UUIDs may be generated using nextRandom or your favorite instance of Random.
  • We have an implementation of generating a UUID from the hardware MAC address and current system time in Data.UUID.V1.
  • For name-based generation of UUIDs using SHA-1 hashing see Data.UUID.V5.

Synopsis

Documentation

data UUID :: * #

The UUID type. A Random instance is provided which produces version 4 UUIDs as specified in RFC 4122. The Storable and Binary instances are compatible with RFC 4122, storing the fields in network order as 16 bytes.

Instances

Eq UUID 

Methods

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

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

Data 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 

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 #

Read UUID 
Show UUID 

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Storable UUID 

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

Binary UUID 

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 

Methods

rnf :: UUID -> () #

Hashable UUID 

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

Random UUID 

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] #

randomRIO :: (UUID, UUID) -> IO UUID #

randomIO :: IO UUID #

toString :: UUID -> String #

Convert a UUID into a hypenated string using lower-case letters. Example:

 toString <$> fromString "550e8400-e29b-41d4-a716-446655440000"

fromString :: String -> Maybe UUID #

If the passed in String can be parsed as a UUID, it will be. The hyphens may not be omitted. Example:

 fromString "c2cc10e1-57d6-4b6f-9899-38d972112d8c"

Hex digits may be upper or lower-case.

toText :: UUID -> Text #

Convert a UUID into a hyphentated string using lower-case letters.

fromText :: Text -> Maybe UUID #

If the passed in Text can be parsed as an ASCII representation of a UUID, it will be. The hyphens may not be omitted.

toASCIIBytes :: UUID -> ByteString #

Convert a UUID into a hyphentated string using lower-case letters, packed as ASCII bytes into ByteString.

This should be equivalent to toString with pack.

fromASCIIBytes :: ByteString -> Maybe UUID #

If the passed in ByteString can be parsed as an ASCII representation of a UUID, it will be. The hyphens may not be omitted.

This should be equivalent to fromString with unpack.

toLazyASCIIBytes :: UUID -> ByteString #

Similar to toASCIIBytes except we produce a lazy ByteString.

fromLazyASCIIBytes :: ByteString -> Maybe UUID #

Similar to fromASCIIBytes except parses from a lazy ByteString.

toByteString :: UUID -> ByteString #

Encode a UUID into a ByteString in network order.

fromByteString :: ByteString -> Maybe UUID #

Extract a UUID from a ByteString in network byte order. The argument must be 16 bytes long, otherwise Nothing is returned.

toWords :: UUID -> (Word32, Word32, Word32, Word32) #

Covert a UUID into a sequence of Word32 values. Useful for when you need to serialize a UUID and neither Storable nor Binary are appropriate. Introduced in version 1.2.2.

fromWords :: Word32 -> Word32 -> Word32 -> Word32 -> UUID #

Create a UUID from a sequence of Word32. The opposite of toWords. Useful when you need a total function for constructing UUID values. Introduced in version 1.2.2.

null :: UUID -> Bool #

Returns true if the passed-in UUID is the nil UUID.

nil :: UUID #

The nil UUID, as defined in RFC 4122. It is a UUID of all zeros. null u iff u == nil.