| Copyright | (c) 2017-2018 Herbert Valerio Riedel (c) 20082012 Antoine Latter | 
|---|---|
| License | BSD-style | 
| Maintainer | [email protected] | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
Data.UUID.Types
Description
This library is useful for comparing, parsing and printing Universally Unique Identifiers (UUID). See RFC 4122 for the specification.
Synopsis
- data UUID
- nil :: UUID
- null :: UUID -> Bool
- toString :: UUID -> String
- fromString :: String -> Maybe UUID
- toText :: UUID -> Text
- fromText :: Text -> Maybe UUID
- toASCIIBytes :: UUID -> ByteString
- fromASCIIBytes :: ByteString -> Maybe UUID
- toLazyASCIIBytes :: UUID -> ByteString
- fromLazyASCIIBytes :: ByteString -> Maybe UUID
- toByteString :: UUID -> ByteString
- fromByteString :: ByteString -> Maybe UUID
- toWords :: UUID -> (Word32, Word32, Word32, Word32)
- fromWords :: Word32 -> Word32 -> Word32 -> Word32 -> UUID
- toWords64 :: UUID -> (Word64, Word64)
- fromWords64 :: Word64 -> Word64 -> UUID
The UUID Type
Type representing Universally Unique Identifiers (UUID) as specified in RFC 4122.
Instances
| Data UUID Source # | |
| Defined in Data.UUID.Types.Internal 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 # 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 :: forall r r'. (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 # | |
| Storable UUID Source # | This  | 
| Defined in Data.UUID.Types.Internal | |
| Read UUID Source # | |
| Show UUID Source # | Pretty prints a  
 | 
| Binary UUID Source # | This  | 
| NFData UUID Source # | |
| Defined in Data.UUID.Types.Internal | |
| Eq UUID Source # | |
| Ord UUID Source # | |
| Hashable UUID Source # | |
| Defined in Data.UUID.Types.Internal | |
| Random UUID Source # | This  | 
| Uniform UUID Source # | |
| Defined in Data.UUID.Types.Internal Methods uniformM :: StatefulGen g m => g -> m UUID # | |
| Lift UUID Source # | |
Nil UUID
Textual Representation
toString :: UUID -> String Source #
Convert a UUID into a hypenated string using lower-case letters. Example:
>>>toString <$> fromString "550e8400-e29b-41d4-a716-446655440000"Just "550e8400-e29b-41d4-a716-446655440000"
toASCIIBytes :: UUID -> ByteString Source #
Convert a UUID into a hyphentated string using lower-case letters, packed
   as ASCII bytes into ByteString.
fromASCIIBytes :: ByteString -> Maybe UUID Source #
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 Source #
Similar to toASCIIBytes except we produce a lazy ByteString.
fromLazyASCIIBytes :: ByteString -> Maybe UUID Source #
Similar to fromASCIIBytes except parses from a lazy ByteString.
Binary Representation
toByteString :: UUID -> ByteString Source #
Encode a UUID into a ByteString in network order.
This uses the same encoding as the Binary instance.
fromByteString :: ByteString -> Maybe UUID Source #
Extract a UUID from a ByteString in network byte order.
 The argument must be 16 bytes long, otherwise Nothing is returned.
Integer Representation
toWords :: UUID -> (Word32, Word32, Word32, Word32) Source #
Convert a UUID into a sequence of Word32 values.
 Useful for when you need to serialize a UUID and
 neither Storable nor Binary are appropriate.
>>>toWords <$> fromString "550e8400-e29b-41d4-a716-446655440000"Just (1427014656,3801825748,2803254374,1430519808)
See also toWords64.
Since: uuid-1.2.2
Since: 1.0.0
fromWords :: Word32 -> Word32 -> Word32 -> Word32 -> UUID Source #
Create a UUID from a sequence of Word32. The
 inverse of toWords. Useful when you need a total
 function for constructing UUID values.
See also fromWords64.
Since: uuid-1.2.2
Since: 1.0.0