{-# LANGUAGE DeriveDataTypeable, TypeFamilies, CPP #-}
{-# OPTIONS_HADDOCK hide #-}
module Data.UUID.Types.Internal
(UUID(..)
,null
,nil
,fromByteString
,toByteString
,fromString
,toString
,fromText
,toText
,fromWords
,toWords
,toList
,buildFromBytes
,buildFromWords
,fromASCIIBytes
,toASCIIBytes
,fromLazyASCIIBytes
,toLazyASCIIBytes
,UnpackedUUID(..)
,pack
,unpack
) where
import Prelude hiding (null)
import Control.Applicative ((<*>))
import Control.DeepSeq (NFData(..))
import Control.Monad (liftM4, guard)
import Data.Functor ((<$>))
import Data.Char
import Data.Bits
import Data.Hashable
import Data.List (elemIndices)
import Foreign.Ptr (Ptr)
#if MIN_VERSION_base(4,0,0)
import Data.Data
#else
import Data.Generics.Basics
#endif
import Foreign.Storable
import Data.Binary
import Data.Binary.Put
import Data.Binary.Get
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as BI
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Unsafe as BU
import Data.Text (Text)
import qualified Data.Text as T
import Data.UUID.Types.Internal.Builder
import System.Random
data UUID
= UUID
{-# UNPACK #-} !Word32
{-# UNPACK #-} !Word32
{-# UNPACK #-} !Word32
{-# UNPACK #-} !Word32
deriving (UUID -> UUID -> Bool
(UUID -> UUID -> Bool) -> (UUID -> UUID -> Bool) -> Eq UUID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UUID -> UUID -> Bool
$c/= :: UUID -> UUID -> Bool
== :: UUID -> UUID -> Bool
$c== :: UUID -> UUID -> Bool
Eq, Eq UUID
Eq UUID =>
(UUID -> UUID -> Ordering)
-> (UUID -> UUID -> Bool)
-> (UUID -> UUID -> Bool)
-> (UUID -> UUID -> Bool)
-> (UUID -> UUID -> Bool)
-> (UUID -> UUID -> UUID)
-> (UUID -> UUID -> UUID)
-> Ord UUID
UUID -> UUID -> Bool
UUID -> UUID -> Ordering
UUID -> UUID -> UUID
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UUID -> UUID -> UUID
$cmin :: UUID -> UUID -> UUID
max :: UUID -> UUID -> UUID
$cmax :: UUID -> UUID -> UUID
>= :: UUID -> UUID -> Bool
$c>= :: UUID -> UUID -> Bool
> :: UUID -> UUID -> Bool
$c> :: UUID -> UUID -> Bool
<= :: UUID -> UUID -> Bool
$c<= :: UUID -> UUID -> Bool
< :: UUID -> UUID -> Bool
$c< :: UUID -> UUID -> Bool
compare :: UUID -> UUID -> Ordering
$ccompare :: UUID -> UUID -> Ordering
$cp1Ord :: Eq UUID
Ord, Typeable)
toWords :: UUID -> (Word32, Word32, Word32, Word32)
toWords :: UUID -> (Word32, Word32, Word32, Word32)
toWords (UUID w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3 w4 :: Word32
w4) = (Word32
w1, Word32
w2, Word32
w3, Word32
w4)
fromWords :: Word32 -> Word32 -> Word32 -> Word32 -> UUID
fromWords :: Word32 -> Word32 -> Word32 -> Word32 -> UUID
fromWords = Word32 -> Word32 -> Word32 -> Word32 -> UUID
UUID
data UnpackedUUID =
UnpackedUUID {
UnpackedUUID -> Word32
time_low :: Word32
, UnpackedUUID -> Word16
time_mid :: Word16
, UnpackedUUID -> Word16
time_hi_and_version :: Word16
, UnpackedUUID -> Word8
clock_seq_hi_res :: Word8
, UnpackedUUID -> Word8
clock_seq_low :: Word8
, UnpackedUUID -> Word8
node_0 :: Word8
, UnpackedUUID -> Word8
node_1 :: Word8
, UnpackedUUID -> Word8
node_2 :: Word8
, UnpackedUUID -> Word8
node_3 :: Word8
, UnpackedUUID -> Word8
node_4 :: Word8
, UnpackedUUID -> Word8
node_5 :: Word8
}
deriving (ReadPrec [UnpackedUUID]
ReadPrec UnpackedUUID
Int -> ReadS UnpackedUUID
ReadS [UnpackedUUID]
(Int -> ReadS UnpackedUUID)
-> ReadS [UnpackedUUID]
-> ReadPrec UnpackedUUID
-> ReadPrec [UnpackedUUID]
-> Read UnpackedUUID
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnpackedUUID]
$creadListPrec :: ReadPrec [UnpackedUUID]
readPrec :: ReadPrec UnpackedUUID
$creadPrec :: ReadPrec UnpackedUUID
readList :: ReadS [UnpackedUUID]
$creadList :: ReadS [UnpackedUUID]
readsPrec :: Int -> ReadS UnpackedUUID
$creadsPrec :: Int -> ReadS UnpackedUUID
Read, Int -> UnpackedUUID -> ShowS
[UnpackedUUID] -> ShowS
UnpackedUUID -> String
(Int -> UnpackedUUID -> ShowS)
-> (UnpackedUUID -> String)
-> ([UnpackedUUID] -> ShowS)
-> Show UnpackedUUID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnpackedUUID] -> ShowS
$cshowList :: [UnpackedUUID] -> ShowS
show :: UnpackedUUID -> String
$cshow :: UnpackedUUID -> String
showsPrec :: Int -> UnpackedUUID -> ShowS
$cshowsPrec :: Int -> UnpackedUUID -> ShowS
Show, UnpackedUUID -> UnpackedUUID -> Bool
(UnpackedUUID -> UnpackedUUID -> Bool)
-> (UnpackedUUID -> UnpackedUUID -> Bool) -> Eq UnpackedUUID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnpackedUUID -> UnpackedUUID -> Bool
$c/= :: UnpackedUUID -> UnpackedUUID -> Bool
== :: UnpackedUUID -> UnpackedUUID -> Bool
$c== :: UnpackedUUID -> UnpackedUUID -> Bool
Eq, Eq UnpackedUUID
Eq UnpackedUUID =>
(UnpackedUUID -> UnpackedUUID -> Ordering)
-> (UnpackedUUID -> UnpackedUUID -> Bool)
-> (UnpackedUUID -> UnpackedUUID -> Bool)
-> (UnpackedUUID -> UnpackedUUID -> Bool)
-> (UnpackedUUID -> UnpackedUUID -> Bool)
-> (UnpackedUUID -> UnpackedUUID -> UnpackedUUID)
-> (UnpackedUUID -> UnpackedUUID -> UnpackedUUID)
-> Ord UnpackedUUID
UnpackedUUID -> UnpackedUUID -> Bool
UnpackedUUID -> UnpackedUUID -> Ordering
UnpackedUUID -> UnpackedUUID -> UnpackedUUID
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UnpackedUUID -> UnpackedUUID -> UnpackedUUID
$cmin :: UnpackedUUID -> UnpackedUUID -> UnpackedUUID
max :: UnpackedUUID -> UnpackedUUID -> UnpackedUUID
$cmax :: UnpackedUUID -> UnpackedUUID -> UnpackedUUID
>= :: UnpackedUUID -> UnpackedUUID -> Bool
$c>= :: UnpackedUUID -> UnpackedUUID -> Bool
> :: UnpackedUUID -> UnpackedUUID -> Bool
$c> :: UnpackedUUID -> UnpackedUUID -> Bool
<= :: UnpackedUUID -> UnpackedUUID -> Bool
$c<= :: UnpackedUUID -> UnpackedUUID -> Bool
< :: UnpackedUUID -> UnpackedUUID -> Bool
$c< :: UnpackedUUID -> UnpackedUUID -> Bool
compare :: UnpackedUUID -> UnpackedUUID -> Ordering
$ccompare :: UnpackedUUID -> UnpackedUUID -> Ordering
$cp1Ord :: Eq UnpackedUUID
Ord)
unpack :: UUID -> UnpackedUUID
unpack :: UUID -> UnpackedUUID
unpack (UUID w0 :: Word32
w0 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3) =
ByteSink
Word32
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID
build ByteSink
Word32
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
-> Word32
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ Word32
w0 ByteSink
Word32
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
-> Word32
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ Word32
w1 ByteSink Word32 (Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID)
-> Word32 -> Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ Word32
w2 ByteSink Word32 UnpackedUUID -> Word32 -> UnpackedUUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ Word32
w3
where
build :: Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID
build x0 :: Word8
x0 x1 :: Word8
x1 x2 :: Word8
x2 x3 :: Word8
x3 x4 :: Word8
x4 x5 :: Word8
x5 x6 :: Word8
x6 x7 :: Word8
x7 x8 :: Word8
x8 x9 :: Word8
x9 xA :: Word8
xA xB :: Word8
xB xC :: Word8
xC xD :: Word8
xD xE :: Word8
xE xF :: Word8
xF =
UnpackedUUID :: Word32
-> Word16
-> Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID
UnpackedUUID {
time_low :: Word32
time_low = Word8 -> Word8 -> Word8 -> Word8 -> Word32
word Word8
x0 Word8
x1 Word8
x2 Word8
x3
, time_mid :: Word16
time_mid = Word8 -> Word8 -> Word16
w8to16 Word8
x4 Word8
x5
, time_hi_and_version :: Word16
time_hi_and_version = Word8 -> Word8 -> Word16
w8to16 Word8
x6 Word8
x7
, clock_seq_hi_res :: Word8
clock_seq_hi_res = Word8
x8
, clock_seq_low :: Word8
clock_seq_low = Word8
x9
, node_0 :: Word8
node_0 = Word8
xA
, node_1 :: Word8
node_1 = Word8
xB
, node_2 :: Word8
node_2 = Word8
xC
, node_3 :: Word8
node_3 = Word8
xD
, node_4 :: Word8
node_4 = Word8
xE
, node_5 :: Word8
node_5 = Word8
xF
}
pack :: UnpackedUUID -> UUID
pack :: UnpackedUUID -> UUID
pack unpacked :: UnpackedUUID
unpacked =
ByteSink
Word32
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID)
Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
makeFromBytes ByteSink
Word32
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID)
-> Word32
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word32
time_low UnpackedUUID
unpacked)
ByteSink
Word16
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID)
-> Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word16
time_mid UnpackedUUID
unpacked)
ByteSink
Word16
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID)
-> Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word16
time_hi_and_version UnpackedUUID
unpacked)
ByteSink
Word8
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UUID)
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
clock_seq_hi_res UnpackedUUID
unpacked)
ByteSink
Word8 (Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UUID)
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
clock_seq_low UnpackedUUID
unpacked)
ByteSink Word8 (Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UUID)
-> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
node_0 UnpackedUUID
unpacked) ByteSink Word8 (Word8 -> Word8 -> Word8 -> Word8 -> UUID)
-> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
node_1 UnpackedUUID
unpacked)
ByteSink Word8 (Word8 -> Word8 -> Word8 -> UUID)
-> Word8 -> Word8 -> Word8 -> Word8 -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
node_2 UnpackedUUID
unpacked) ByteSink Word8 (Word8 -> Word8 -> UUID)
-> Word8 -> Word8 -> Word8 -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
node_3 UnpackedUUID
unpacked)
ByteSink Word8 (Word8 -> UUID) -> Word8 -> Word8 -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
node_4 UnpackedUUID
unpacked) ByteSink Word8 UUID -> Word8 -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (UnpackedUUID -> Word8
node_5 UnpackedUUID
unpacked)
word :: Word8 -> Word8 -> Word8 -> Word8 -> Word32
word :: Word8 -> Word8 -> Word8 -> Word8 -> Word32
word a :: Word8
a b :: Word8
b c :: Word8
c d :: Word8
d = (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
a Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` 24)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` 16)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` 8)
Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. (Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
d )
byte :: Int -> Word32 -> Word8
byte :: Int -> Word32 -> Word8
byte i :: Int
i w :: Word32
w = Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8))
w8to16 :: Word8 -> Word8 -> Word16
w8to16 :: Word8 -> Word8 -> Word16
w8to16 w0s :: Word8
w0s w1s :: Word8
w1s =
(Word16
w0 Word16 -> Int -> Word16
forall a. Bits a => a -> Int -> a
`shiftL` 8) Word16 -> Word16 -> Word16
forall a. Bits a => a -> a -> a
.|. Word16
w1
where
w0 :: Word16
w0 = Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w0s
w1 :: Word16
w1 = Word8 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
w1s
makeFromBytes :: Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> UUID
makeFromBytes :: Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
makeFromBytes b0 :: Word8
b0 b1 :: Word8
b1 b2 :: Word8
b2 b3 :: Word8
b3 b4 :: Word8
b4 b5 :: Word8
b5 b6 :: Word8
b6 b7 :: Word8
b7 b8 :: Word8
b8 b9 :: Word8
b9 ba :: Word8
ba bb :: Word8
bb bc :: Word8
bc bd :: Word8
bd be :: Word8
be bf :: Word8
bf
= Word32 -> Word32 -> Word32 -> Word32 -> UUID
UUID Word32
w0 Word32
w1 Word32
w2 Word32
w3
where w0 :: Word32
w0 = Word8 -> Word8 -> Word8 -> Word8 -> Word32
word Word8
b0 Word8
b1 Word8
b2 Word8
b3
w1 :: Word32
w1 = Word8 -> Word8 -> Word8 -> Word8 -> Word32
word Word8
b4 Word8
b5 Word8
b6 Word8
b7
w2 :: Word32
w2 = Word8 -> Word8 -> Word8 -> Word8 -> Word32
word Word8
b8 Word8
b9 Word8
ba Word8
bb
w3 :: Word32
w3 = Word8 -> Word8 -> Word8 -> Word8 -> Word32
word Word8
bc Word8
bd Word8
be Word8
bf
makeFromWords :: Word32 -> Word32 -> Word32 -> Word32 -> UUID
makeFromWords :: Word32 -> Word32 -> Word32 -> Word32 -> UUID
makeFromWords = Word32 -> Word32 -> Word32 -> Word32 -> UUID
UUID
buildFromBytes :: Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> Word8 -> Word8 -> Word8 -> Word8
-> UUID
buildFromBytes :: Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
buildFromBytes v :: Word8
v b0 :: Word8
b0 b1 :: Word8
b1 b2 :: Word8
b2 b3 :: Word8
b3 b4 :: Word8
b4 b5 :: Word8
b5 b6 :: Word8
b6 b7 :: Word8
b7 b8 :: Word8
b8 b9 :: Word8
b9 ba :: Word8
ba bb :: Word8
bb bc :: Word8
bc bd :: Word8
bd be :: Word8
be bf :: Word8
bf =
Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
makeFromBytes Word8
b0 Word8
b1 Word8
b2 Word8
b3 Word8
b4 Word8
b5 Word8
b6' Word8
b7 Word8
b8' Word8
b9 Word8
ba Word8
bb Word8
bc Word8
bd Word8
be Word8
bf
where b6' :: Word8
b6' = Word8
b6 Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. 0x0f Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. (Word8
v Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`shiftL` 4)
b8' :: Word8
b8' = Word8
b8 Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. 0x3f Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. 0x80
buildFromWords :: Word8 -> Word32 -> Word32 -> Word32 -> Word32 -> UUID
buildFromWords :: Word8 -> Word32 -> Word32 -> Word32 -> Word32 -> UUID
buildFromWords v :: Word8
v w0 :: Word32
w0 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3 = Word32 -> Word32 -> Word32 -> Word32 -> UUID
makeFromWords Word32
w0 Word32
w1' Word32
w2' Word32
w3
where w1' :: Word32
w1' = Word32
w1 Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. 0xffff0fff Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. ((Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
v) Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` 12)
w2' :: Word32
w2' = Word32
w2 Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. 0x3fffffff Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. 0x80000000
toList :: UUID -> [Word8]
toList :: UUID -> [Word8]
toList (UUID w0 :: Word32
w0 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3) =
[Int -> Word32 -> Word8
byte 3 Word32
w0, Int -> Word32 -> Word8
byte 2 Word32
w0, Int -> Word32 -> Word8
byte 1 Word32
w0, Int -> Word32 -> Word8
byte 0 Word32
w0,
Int -> Word32 -> Word8
byte 3 Word32
w1, Int -> Word32 -> Word8
byte 2 Word32
w1, Int -> Word32 -> Word8
byte 1 Word32
w1, Int -> Word32 -> Word8
byte 0 Word32
w1,
Int -> Word32 -> Word8
byte 3 Word32
w2, Int -> Word32 -> Word8
byte 2 Word32
w2, Int -> Word32 -> Word8
byte 1 Word32
w2, Int -> Word32 -> Word8
byte 0 Word32
w2,
Int -> Word32 -> Word8
byte 3 Word32
w3, Int -> Word32 -> Word8
byte 2 Word32
w3, Int -> Word32 -> Word8
byte 1 Word32
w3, Int -> Word32 -> Word8
byte 0 Word32
w3]
fromList :: [Word8] -> Maybe UUID
fromList :: [Word8] -> Maybe UUID
fromList [b0 :: Word8
b0, b1 :: Word8
b1, b2 :: Word8
b2, b3 :: Word8
b3, b4 :: Word8
b4, b5 :: Word8
b5, b6 :: Word8
b6, b7 :: Word8
b7, b8 :: Word8
b8, b9 :: Word8
b9, ba :: Word8
ba, bb :: Word8
bb, bc :: Word8
bc, bd :: Word8
bd, be :: Word8
be, bf :: Word8
bf] =
UUID -> Maybe UUID
forall a. a -> Maybe a
Just (UUID -> Maybe UUID) -> UUID -> Maybe UUID
forall a b. (a -> b) -> a -> b
$ Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
makeFromBytes Word8
b0 Word8
b1 Word8
b2 Word8
b3 Word8
b4 Word8
b5 Word8
b6 Word8
b7 Word8
b8 Word8
b9 Word8
ba Word8
bb Word8
bc Word8
bd Word8
be Word8
bf
fromList _ = Maybe UUID
forall a. Maybe a
Nothing
null :: UUID -> Bool
null :: UUID -> Bool
null = (UUID -> UUID -> Bool
forall a. Eq a => a -> a -> Bool
== UUID
nil)
nil :: UUID
nil :: UUID
nil = Word32 -> Word32 -> Word32 -> Word32 -> UUID
UUID 0 0 0 0
fromByteString :: BL.ByteString -> Maybe UUID
fromByteString :: ByteString -> Maybe UUID
fromByteString = [Word8] -> Maybe UUID
fromList ([Word8] -> Maybe UUID)
-> (ByteString -> [Word8]) -> ByteString -> Maybe UUID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Word8]
BL.unpack
toByteString :: UUID -> BL.ByteString
toByteString :: UUID -> ByteString
toByteString = [Word8] -> ByteString
BL.pack ([Word8] -> ByteString) -> (UUID -> [Word8]) -> UUID -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> [Word8]
toList
fromString :: String -> Maybe UUID
fromString :: String -> Maybe UUID
fromString xs :: String
xs | Bool
validFmt = String -> Maybe UUID
fromString' String
xs
| Bool
otherwise = Maybe UUID
forall a. Maybe a
Nothing
where validFmt :: Bool
validFmt = Char -> String -> [Int]
forall a. Eq a => a -> [a] -> [Int]
elemIndices '-' String
xs [Int] -> [Int] -> Bool
forall a. Eq a => a -> a -> Bool
== [8,13,18,23]
fromString' :: String -> Maybe UUID
fromString' :: String -> Maybe UUID
fromString' s0 :: String
s0 = do
(w0 :: Word32
w0, s1 :: String
s1) <- String -> Maybe (Word32, String)
hexWord String
s0
(w1 :: Word32
w1, s2 :: String
s2) <- String -> Maybe (Word32, String)
hexWord String
s1
(w2 :: Word32
w2, s3 :: String
s3) <- String -> Maybe (Word32, String)
hexWord String
s2
(w3 :: Word32
w3, s4 :: String
s4) <- String -> Maybe (Word32, String)
hexWord String
s3
if String
s4 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= "" then Maybe UUID
forall a. Maybe a
Nothing
else UUID -> Maybe UUID
forall a. a -> Maybe a
Just (UUID -> Maybe UUID) -> UUID -> Maybe UUID
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> Word32 -> Word32 -> UUID
UUID Word32
w0 Word32
w1 Word32
w2 Word32
w3
where hexWord :: String -> Maybe (Word32, String)
hexWord :: String -> Maybe (Word32, String)
hexWord s :: String
s = (Word32, String) -> Maybe (Word32, String)
forall a. a -> Maybe a
Just (0, String
s) Maybe (Word32, String)
-> ((Word32, String) -> Maybe (Word32, String))
-> Maybe (Word32, String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Word32, String) -> Maybe (Word32, String)
hexByte Maybe (Word32, String)
-> ((Word32, String) -> Maybe (Word32, String))
-> Maybe (Word32, String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Word32, String) -> Maybe (Word32, String)
hexByte
Maybe (Word32, String)
-> ((Word32, String) -> Maybe (Word32, String))
-> Maybe (Word32, String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Word32, String) -> Maybe (Word32, String)
hexByte Maybe (Word32, String)
-> ((Word32, String) -> Maybe (Word32, String))
-> Maybe (Word32, String)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Word32, String) -> Maybe (Word32, String)
hexByte
hexByte :: (Word32, String) -> Maybe (Word32, String)
hexByte :: (Word32, String) -> Maybe (Word32, String)
hexByte (w :: Word32
w, '-':ds :: String
ds) = (Word32, String) -> Maybe (Word32, String)
hexByte (Word32
w, String
ds)
hexByte (w :: Word32
w, hi :: Char
hi:lo :: Char
lo:ds :: String
ds)
| Bool
bothHex = (Word32, String) -> Maybe (Word32, String)
forall a. a -> Maybe a
Just ((Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftL` 8) Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32
octet, String
ds)
| Bool
otherwise = Maybe (Word32, String)
forall a. Maybe a
Nothing
where bothHex :: Bool
bothHex = Char -> Bool
isHexDigit Char
hi Bool -> Bool -> Bool
&& Char -> Bool
isHexDigit Char
lo
octet :: Word32
octet = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Char -> Int
digitToInt Char
hi Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Char -> Int
digitToInt Char
lo)
hexByte _ = Maybe (Word32, String)
forall a. Maybe a
Nothing
toString :: UUID -> String
toString :: UUID -> String
toString (UUID w0 :: Word32
w0 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3) = Word32 -> ShowS
hexw Word32
w0 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Word32 -> ShowS
hexw' Word32
w1 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Word32 -> ShowS
hexw' Word32
w2 ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Word32 -> ShowS
hexw Word32
w3 ""
where hexw :: Word32 -> String -> String
hexw :: Word32 -> ShowS
hexw w :: Word32
w s :: String
s = Word32 -> Int -> Char
hexn Word32
w 28 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 24 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 20 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 16
Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 12 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 8 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 4 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 0 Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
hexw' :: Word32 -> String -> String
hexw' :: Word32 -> ShowS
hexw' w :: Word32
w s :: String
s = '-' Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 28 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 24 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 20 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 16
Char -> ShowS
forall a. a -> [a] -> [a]
: '-' Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 12 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 8 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 4 Char -> ShowS
forall a. a -> [a] -> [a]
: Word32 -> Int -> Char
hexn Word32
w 0 Char -> ShowS
forall a. a -> [a] -> [a]
: String
s
hexn :: Word32 -> Int -> Char
hexn :: Word32 -> Int -> Char
hexn w :: Word32
w r :: Int
r = Int -> Char
intToDigit (Int -> Char) -> Int -> Char
forall a b. (a -> b) -> a -> b
$ Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
r) Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. 0xf)
fromText :: Text -> Maybe UUID
fromText :: Text -> Maybe UUID
fromText = String -> Maybe UUID
fromString (String -> Maybe UUID) -> (Text -> String) -> Text -> Maybe UUID
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
toText :: UUID -> Text
toText :: UUID -> Text
toText = String -> Text
T.pack (String -> Text) -> (UUID -> String) -> UUID -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
toString
toASCIIBytes :: UUID -> B.ByteString
toASCIIBytes :: UUID -> ByteString
toASCIIBytes uuid :: UUID
uuid = Int -> (Ptr Word8 -> IO ()) -> ByteString
BI.unsafeCreate 36 (UUID -> Ptr Word8 -> IO ()
pokeASCII UUID
uuid)
pokeASCII :: UUID -> Ptr Word8 -> IO ()
pokeASCII :: UUID -> Ptr Word8 -> IO ()
pokeASCII uuid :: UUID
uuid ptr :: Ptr Word8
ptr = do
Int -> IO ()
pokeDash 8
Int -> IO ()
pokeDash 13
Int -> IO ()
pokeDash 18
Int -> IO ()
pokeDash 23
Int -> Word32 -> IO ()
pokeSingle 0 Word32
w0
Int -> Word32 -> IO ()
pokeDouble 9 Word32
w1
Int -> Word32 -> IO ()
pokeDouble 19 Word32
w2
Int -> Word32 -> IO ()
pokeSingle 28 Word32
w3
where
(w0 :: Word32
w0, w1 :: Word32
w1, w2 :: Word32
w2, w3 :: Word32
w3) = UUID -> (Word32, Word32, Word32, Word32)
toWords UUID
uuid
pokeDash :: Int -> IO ()
pokeDash ix :: Int
ix = Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
ix 45
pokeSingle :: Int -> Word32 -> IO ()
pokeSingle ix :: Int
ix w :: Word32
w = do
Int -> Word32 -> Int -> IO ()
pokeWord Int
ix Word32
w 28
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1) Word32
w 24
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 2) Word32
w 20
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 3) Word32
w 16
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 4) Word32
w 12
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 5) Word32
w 8
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 6) Word32
w 4
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 7) Word32
w 0
pokeDouble :: Int -> Word32 -> IO ()
pokeDouble ix :: Int
ix w :: Word32
w = do
Int -> Word32 -> Int -> IO ()
pokeWord Int
ix Word32
w 28
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1) Word32
w 24
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 2) Word32
w 20
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 3) Word32
w 16
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 5) Word32
w 12
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 6) Word32
w 8
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 7) Word32
w 4
Int -> Word32 -> Int -> IO ()
pokeWord (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 8) Word32
w 0
pokeWord :: Int -> Word32 -> Int -> IO ()
pokeWord ix :: Int
ix w :: Word32
w r :: Int
r =
Ptr Word8 -> Int -> Word8 -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr Word8
ptr Int
ix (Word32 -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word32
toDigit ((Word32
w Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
`shiftR` Int
r) Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. 0xf)))
toDigit :: Word32 -> Word32
toDigit :: Word32 -> Word32
toDigit w :: Word32
w = if Word32
w Word32 -> Word32 -> Bool
forall a. Ord a => a -> a -> Bool
< 10 then 48 Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
w else 97 Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
w Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
- 10
fromASCIIBytes :: B.ByteString -> Maybe UUID
fromASCIIBytes :: ByteString -> Maybe UUID
fromASCIIBytes bs :: ByteString
bs = do
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
wellFormed
Word32 -> Word32 -> Word32 -> Word32 -> UUID
fromWords (Word32 -> Word32 -> Word32 -> Word32 -> UUID)
-> Maybe Word32 -> Maybe (Word32 -> Word32 -> Word32 -> UUID)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Maybe Word32
single 0 Maybe (Word32 -> Word32 -> Word32 -> UUID)
-> Maybe Word32 -> Maybe (Word32 -> Word32 -> UUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Int -> Maybe Word32
double 9 14 Maybe (Word32 -> Word32 -> UUID)
-> Maybe Word32 -> Maybe (Word32 -> UUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Int -> Maybe Word32
double 19 24 Maybe (Word32 -> UUID) -> Maybe Word32 -> Maybe UUID
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Maybe Word32
single 28
where
dashIx :: ByteString -> Int -> Bool
dashIx bs' :: ByteString
bs' ix :: Int
ix = ByteString -> Int -> Word8
BU.unsafeIndex ByteString
bs' Int
ix Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== 45
wellFormed :: Bool
wellFormed =
ByteString -> Int
B.length ByteString
bs Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 36 Bool -> Bool -> Bool
&& ByteString -> Int -> Bool
dashIx ByteString
bs 8 Bool -> Bool -> Bool
&& ByteString -> Int -> Bool
dashIx ByteString
bs 13 Bool -> Bool -> Bool
&&
ByteString -> Int -> Bool
dashIx ByteString
bs 18 Bool -> Bool -> Bool
&& ByteString -> Int -> Bool
dashIx ByteString
bs 23
single :: Int -> Maybe Word32
single ix :: Int
ix = Word32 -> Word32 -> Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a -> a -> a
combine (Word32 -> Word32 -> Word32 -> Word32 -> Word32)
-> Maybe Word32 -> Maybe (Word32 -> Word32 -> Word32 -> Word32)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Maybe Word32
octet Int
ix Maybe (Word32 -> Word32 -> Word32 -> Word32)
-> Maybe Word32 -> Maybe (Word32 -> Word32 -> Word32)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Maybe Word32
octet (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 2)
Maybe (Word32 -> Word32 -> Word32)
-> Maybe Word32 -> Maybe (Word32 -> Word32)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Maybe Word32
octet (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 4) Maybe (Word32 -> Word32) -> Maybe Word32 -> Maybe Word32
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Maybe Word32
octet (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 6)
double :: Int -> Int -> Maybe Word32
double ix0 :: Int
ix0 ix1 :: Int
ix1 = Word32 -> Word32 -> Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a -> a -> a
combine (Word32 -> Word32 -> Word32 -> Word32 -> Word32)
-> Maybe Word32 -> Maybe (Word32 -> Word32 -> Word32 -> Word32)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Maybe Word32
octet Int
ix0 Maybe (Word32 -> Word32 -> Word32 -> Word32)
-> Maybe Word32 -> Maybe (Word32 -> Word32 -> Word32)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Maybe Word32
octet (Int
ix0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 2)
Maybe (Word32 -> Word32 -> Word32)
-> Maybe Word32 -> Maybe (Word32 -> Word32)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Maybe Word32
octet Int
ix1 Maybe (Word32 -> Word32) -> Maybe Word32 -> Maybe Word32
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> Maybe Word32
octet (Int
ix1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 2)
combine :: a -> a -> a -> a -> a
combine o0 :: a
o0 o1 :: a
o1 o2 :: a
o2 o3 :: a
o3 = a -> Int -> a
forall a. Bits a => a -> Int -> a
shiftL a
o0 24 a -> a -> a
forall a. Bits a => a -> a -> a
.|. a -> Int -> a
forall a. Bits a => a -> Int -> a
shiftL a
o1 16 a -> a -> a
forall a. Bits a => a -> a -> a
.|. a -> Int -> a
forall a. Bits a => a -> Int -> a
shiftL a
o2 8 a -> a -> a
forall a. Bits a => a -> a -> a
.|. a
o3
octet :: Int -> Maybe Word32
octet ix :: Int
ix = do
Word32
hi <- Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word32) -> Maybe Word8 -> Maybe Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Maybe Word8
toDigit (ByteString -> Int -> Word8
BU.unsafeIndex ByteString
bs Int
ix)
Word32
lo <- Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word32) -> Maybe Word8 -> Maybe Word32
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word8 -> Maybe Word8
toDigit (ByteString -> Int -> Word8
BU.unsafeIndex ByteString
bs (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1))
Word32 -> Maybe Word32
forall (m :: * -> *) a. Monad m => a -> m a
return (16 Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
* Word32
hi Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word32
lo)
toDigit :: Word8 -> Maybe Word8
toDigit :: Word8 -> Maybe Word8
toDigit w :: Word8
w
| Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= 48 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= 57 = Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- 48)
| Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= 65 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= 70 = Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (10 Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- 65)
| Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= 97 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= 102 = Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (10 Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
w Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
- 97)
| Bool
otherwise = Maybe Word8
forall a. Maybe a
Nothing
toLazyASCIIBytes :: UUID -> BL.ByteString
toLazyASCIIBytes :: UUID -> ByteString
toLazyASCIIBytes =
#if MIN_VERSION_bytestring(0,10,0)
ByteString -> ByteString
BL.fromStrict
#else
BL.fromChunks . return
#endif
(ByteString -> ByteString)
-> (UUID -> ByteString) -> UUID -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> ByteString
toASCIIBytes
fromLazyASCIIBytes :: BL.ByteString -> Maybe UUID
fromLazyASCIIBytes :: ByteString -> Maybe UUID
fromLazyASCIIBytes bs :: ByteString
bs =
if ByteString -> Int64
BL.length ByteString
bs Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== 36 then ByteString -> Maybe UUID
fromASCIIBytes (
#if MIN_VERSION_bytestring(0,10,0)
ByteString -> ByteString
BL.toStrict ByteString
bs
#else
B.concat $ BL.toChunks bs
#endif
) else Maybe UUID
forall a. Maybe a
Nothing
instance Random UUID where
random :: g -> (UUID, g)
random g :: g
g = (Int -> Int -> Int -> Int -> Int -> UUID
fromGenNext Int
w0 Int
w1 Int
w2 Int
w3 Int
w4, g
g4)
where (w0 :: Int
w0, g0 :: g
g0) = g -> (Int, g)
forall g. RandomGen g => g -> (Int, g)
next g
g
(w1 :: Int
w1, g1 :: g
g1) = g -> (Int, g)
forall g. RandomGen g => g -> (Int, g)
next g
g0
(w2 :: Int
w2, g2 :: g
g2) = g -> (Int, g)
forall g. RandomGen g => g -> (Int, g)
next g
g1
(w3 :: Int
w3, g3 :: g
g3) = g -> (Int, g)
forall g. RandomGen g => g -> (Int, g)
next g
g2
(w4 :: Int
w4, g4 :: g
g4) = g -> (Int, g)
forall g. RandomGen g => g -> (Int, g)
next g
g3
randomR :: (UUID, UUID) -> g -> (UUID, g)
randomR _ = g -> (UUID, g)
forall a g. (Random a, RandomGen g) => g -> (a, g)
random
fromGenNext :: Int -> Int -> Int -> Int -> Int -> UUID
fromGenNext :: Int -> Int -> Int -> Int -> Int -> UUID
fromGenNext w0 :: Int
w0 w1 :: Int
w1 w2 :: Int
w2 w3 :: Int
w3 w4 :: Int
w4 =
Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
buildFromBytes 4 ByteSink
ThreeByte
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID)
-> ThreeByte
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (Int -> ThreeByte
ThreeByte Int
w0)
ByteSink
ThreeByte
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID)
-> ThreeByte
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (Int -> ThreeByte
ThreeByte Int
w1)
ByteSink
Int (Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UUID)
-> Int
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ Int
w2
ByteSink ThreeByte (Word8 -> Word8 -> Word8 -> UUID)
-> ThreeByte -> Word8 -> Word8 -> Word8 -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (Int -> ThreeByte
ThreeByte Int
w3)
ByteSink ThreeByte UUID -> ThreeByte -> UUID
forall w g. ByteSource w => ByteSink w g -> w -> g
/-/ (Int -> ThreeByte
ThreeByte Int
w4)
type instance ByteSink ThreeByte g = Takes3Bytes g
newtype ThreeByte = ThreeByte Int
instance ByteSource ThreeByte where
f :: ByteSink ThreeByte g
f /-/ :: ByteSink ThreeByte g -> ThreeByte -> g
/-/ (ThreeByte w :: Int
w) = ByteSink ThreeByte g
Takes3Bytes g
f Word8
b1 Word8
b2 Word8
b3
where b1 :: Word8
b1 = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
w Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` 16)
b2 :: Word8
b2 = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
w Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftR` 8)
b3 :: Word8
b3 = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w
instance NFData UUID where
rnf :: UUID -> ()
rnf = (Word32, Word32, Word32, Word32) -> ()
forall a. NFData a => a -> ()
rnf ((Word32, Word32, Word32, Word32) -> ())
-> (UUID -> (Word32, Word32, Word32, Word32)) -> UUID -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> (Word32, Word32, Word32, Word32)
toWords
instance Hashable UUID where
hash :: UUID -> Int
hash (UUID w0 :: Word32
w0 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3) =
Word32 -> Int
forall a. Hashable a => a -> Int
hash Word32
w0 Int -> Word32 -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Word32
w1
Int -> Word32 -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Word32
w2
Int -> Word32 -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Word32
w3
hashWithSalt :: Int -> UUID -> Int
hashWithSalt s :: Int
s (UUID w0 :: Word32
w0 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3) =
Int
s Int -> Word32 -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Word32
w0
Int -> Word32 -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Word32
w1
Int -> Word32 -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Word32
w2
Int -> Word32 -> Int
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Word32
w3
instance Show UUID where
show :: UUID -> String
show = UUID -> String
toString
instance Read UUID where
readsPrec :: Int -> ReadS UUID
readsPrec _ str :: String
str =
let noSpaces :: String
noSpaces = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
dropWhile Char -> Bool
isSpace String
str
in case String -> Maybe UUID
fromString (Int -> ShowS
forall a. Int -> [a] -> [a]
take 36 String
noSpaces) of
Nothing -> []
Just u :: UUID
u -> [(UUID
u,Int -> ShowS
forall a. Int -> [a] -> [a]
drop 36 String
noSpaces)]
instance Storable UUID where
sizeOf :: UUID -> Int
sizeOf _ = 16
alignment :: UUID -> Int
alignment _ = 4
peekByteOff :: Ptr b -> Int -> IO UUID
peekByteOff p :: Ptr b
p off :: Int
off =
UnpackedUUID -> UUID
pack (UnpackedUUID -> UUID) -> IO UnpackedUUID -> IO UUID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Word32
-> Word16
-> Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID
UnpackedUUID
(Word32
-> Word16
-> Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
-> IO Word32
-> IO
(Word16
-> Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr b -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p Int
off
IO
(Word16
-> Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
-> IO Word16
-> IO
(Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word16
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+4)
IO
(Word16
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
-> IO Word16
-> IO
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word16
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+6)
IO
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
-> IO Word8
-> IO
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+8)
IO
(Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> Word8
-> UnpackedUUID)
-> IO Word8
-> IO
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+9)
IO
(Word8
-> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID)
-> IO Word8
-> IO (Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+10)
IO (Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID)
-> IO Word8
-> IO (Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+11)
IO (Word8 -> Word8 -> Word8 -> Word8 -> UnpackedUUID)
-> IO Word8 -> IO (Word8 -> Word8 -> Word8 -> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+12)
IO (Word8 -> Word8 -> Word8 -> UnpackedUUID)
-> IO Word8 -> IO (Word8 -> Word8 -> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+13)
IO (Word8 -> Word8 -> UnpackedUUID)
-> IO Word8 -> IO (Word8 -> UnpackedUUID)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+14)
IO (Word8 -> UnpackedUUID) -> IO Word8 -> IO UnpackedUUID
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+15)
)
pokeByteOff :: Ptr b -> Int -> UUID -> IO ()
pokeByteOff p :: Ptr b
p off :: Int
off u :: UUID
u =
case UUID -> UnpackedUUID
unpack UUID
u of
(UnpackedUUID x0 :: Word32
x0 x1 :: Word16
x1 x2 :: Word16
x2 x3 :: Word8
x3 x4 :: Word8
x4 x5 :: Word8
x5 x6 :: Word8
x6 x7 :: Word8
x7 x8 :: Word8
x8 x9 :: Word8
x9 x10 :: Word8
x10) ->
do
Ptr b -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p Int
off Word32
x0
Ptr b -> Int -> Word16 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+4) Word16
x1
Ptr b -> Int -> Word16 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+6) Word16
x2
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+8) Word8
x3
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+9) Word8
x4
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+10) Word8
x5
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+11) Word8
x6
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+12) Word8
x7
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+13) Word8
x8
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+14) Word8
x9
Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+15) Word8
x10
instance Binary UUID where
put :: UUID -> Put
put (UUID w0 :: Word32
w0 w1 :: Word32
w1 w2 :: Word32
w2 w3 :: Word32
w3) =
Word32 -> Put
putWord32be Word32
w0 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word32 -> Put
putWord32be Word32
w1 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word32 -> Put
putWord32be Word32
w2 Put -> Put -> Put
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Word32 -> Put
putWord32be Word32
w3
get :: Get UUID
get = (Word32 -> Word32 -> Word32 -> Word32 -> UUID)
-> Get Word32 -> Get Word32 -> Get Word32 -> Get Word32 -> Get UUID
forall (m :: * -> *) a1 a2 a3 a4 r.
Monad m =>
(a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
liftM4 Word32 -> Word32 -> Word32 -> Word32 -> UUID
UUID Get Word32
getWord32be Get Word32
getWord32be Get Word32
getWord32be Get Word32
getWord32be
instance Data UUID where
toConstr :: UUID -> Constr
toConstr uu :: UUID
uu = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
uuidType (UUID -> String
forall a. Show a => a -> String
show UUID
uu) [] (String -> Fixity
forall a. HasCallStack => String -> a
error "fixity")
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UUID
gunfold _ _ = String -> Constr -> c UUID
forall a. HasCallStack => String -> a
error "gunfold"
dataTypeOf :: UUID -> DataType
dataTypeOf _ = DataType
uuidType
uuidType :: DataType
uuidType :: DataType
uuidType = String -> DataType
mkNoRepType "Data.UUID.Types.UUID"
#if !(MIN_VERSION_base(4,2,0))
mkNoRepType :: String -> DataType
mkNoRepType = mkNorepType
#endif