Why doesn't UUID have a Bits instance?

…and you should eschew the name uuid-bits as your 128-bit values won’t be (valid) UUIDs, as noted by @rhendric.


Stretching the Glasgow Haskell Compiler: Nourishing GHC with Domain-Driven Design (2023)


ghci> :m Data.Word
ghci> :i Word128
type Word128 :: *
data Word128 = GHC.Word.W128# GHC.Prim.Word128#
  	-- Defined in ‘GHC.Word’
instance Bounded Word128 -- Defined in ‘GHC.Word’
instance Enum Word128 -- Defined in ‘GHC.Word’
instance Integral Word128 -- Defined in ‘GHC.Word’
instance Num Word128 -- Defined in ‘GHC.Word’
instance Ord Word128 -- Defined in ‘GHC.Word’
instance Read Word128 -- Defined in ‘GHC.Read’
instance Real Word128 -- Defined in ‘GHC.Word’
instance Show Word128 -- Defined in ‘GHC.Word’
instance Eq Word128 -- Defined in ‘GHC.Word’
ghci> 

Nope, I’m gonna be publishing that as uuid-bits because it will allow you to ergonomically interact with uuid's 128 bits.

It’ll come with some real life examples as well:

  • Increase API throughput via client-side query sharding.
    • Easily saturate read throughtput - 8x throughput improvement observed in production.
    • Easily distribute reads across multiple physical servers if necessary.
  • Assign A/B test treatments to billions of users in O(1) time and space.
    • With the ability to incrementally roll out features, scaling from 10% to 20% all the way to 100% with stable A/B selections…all in O(1) time and space.
  • Purely compute N stable and distinct idempotency keys from a single UUID for when the API requires a UUID-looking format.
    • It’s a weird requirement but it does happen!
    • If UUID-esque format isn’t required, just use string concatenation :laughing:

These techniques are definitely useful to have in your “backend engineering” toolkit imo. They can save you implementation time and infrastructure money. And I’m sure there are more “(ab)using UUID bits” techniques out there, so I’d love to try to share the ideas and see if anyone else has their own that they have used!

…including these:

module UUID_Num() where
import Prelude(Int)
import Prelude(Bool(..), (&&), (||), odd, not, error, Integer)
import Prelude(Integral(..), Num(..), Ord(..) ,Read(..), Show(..))
import Data.Bits

-- for testing purposes
-- type UUID = Int

{-
instance Eq UUID where
    (==) = equUU
-}

equUU x y = case x `xor` y of 0 -> True
                              _ -> False
{-
instance Ord UUID where
    (<=) = leqUU
-}

leqUU x y = equUU x y || leqUU' (x `xor` z) (y `xor` z)
              where
                z = x .&. y
                leqUU' 0 0 = True
                leqUU' 1 1 = True
                leqUU' 0 1 = True
                leqUU' 1 0 = False
                leqUU' a b = leqUU' (shiftR a 1) (shiftR b 1)

{-
instance Num UUID where
    (+)         = addUU
    (-)         = subUU
    (*)         = mulUU
    negate      = negUU
    abs         = absUU
    signum      = sgnUU
    fromInteger = iToUU
-}

addUU x 0 = x
addUU x y = addUU (x `xor` y) (shiftL (x .&. y) 1)

subUU x y = addUU x (negUU y)

mulUU _ 0 = 0
mulUU x 1 = x
mulUU x 2 = addUU x x
mulUU x y = addUU x (mulUU x (subUU y 1))

negUU x = addUU 1 (complement x)
absUU x = x
sgnUU _ = 1

iToUU :: Integer -> UUID
iToUU i = iToUU' (i .&. uuToI maxUU)
            where
              iToUU' n | n < 0 = negUU (iToUU' (abs n)) 
              iToUU' 0         = 0
              iToUU' 1         = 1
              iToUU' n         = addUU (if odd n then 1 else 0)
                                       (mulUU 2 (iToUU' (n `div` 2)))

{-
instance Integral UUID where
    toInteger = uuToI
    quotRem   = qtrmUU
-}

uuToI :: UUID -> Integer
uuToI x | x `equUU` maxUU = bit (finiteBitSize x) - 1 
uuToI x                   = (if oddUU x then 1 else 0) + 2 * (uuToI (shiftR x 1))

qtrmUU _ 0               = error "qtrmUU: division by zero"
qtrmUU x y | x `equUU` y = (1, 0)
qtrmUU x y | x `leqUU` y = (0, x)
qtrmUU x y               = let (q, r) = qtrmUU (x `subUU` y) y in
                           (addUU 1 q, r)
 
minUU, maxUU :: UUID
minUU = 0
maxUU = complement 0

oddUU x  = testBit x 0
evenUU x = not (oddUU x)
1 Like

There’s already uuid.

That library isn’t typed or strict enough compared to the goal of uuid-typed.

uuid-typed is meant to ensure only well-formed, to-the-spec UUIDs are generated or created by hand. In theory, it could even allow you to perform bitwise operations on the part of a UUID that is Just Bits while ensuring the resulting UUID conforms to the spec.

It will also be a programming exploration of how to represent the spec in Haskell in a way that automates implementation as much as possible.

I think it’ll make sense once it’s written (I’ll post in Discourse once I get the time to build it. Probably in the next month or two. I’ve been looking for projects with a spec like this to try out some new ideas :grin: )

only well-formed, to-the-spec UUIDs

You mean UnpackedUUID?

Sadly that’s just Internal! I wonder if it should be in the proper API :thinking:

And uuid-typed is meant to be an over-engineered and code-golf-y toy. More an exercise of programming muscle than something optimally practical.

It is.

1 Like

I meant in uuid-types. Feels like a better place for it.

In any case, it doesn’t really affect my plans. Each of the listed libraries don’t quite exist in Haskell and it’ll be fun to build them.

Like I’ve said many times, there’s no “being right” in Haskell design discussions like these. There’s been a lot of moral discussion in this thread about the UUID spec, if bits are an implementation detail, etc. And that’s fun because it shows the large design space such a primitive concept can have.

Haskell has a way of bringing out diversity of ideas in every domain - libraries with opposing philosophies and trade-offs abound. Lack of consensus is my favorite part of being a Haskeller! It’s what attracted me to the language a decade ago in the first place.

But I’m still 100% unconvinced that treating UUIDs as 128-bit words is something that is in the “never do that” category of programming things. I think this thread pretty much confirms it actually.

Nothing stops you from writing and publishing anything you want, of course.

But consider that the problem is not technical, but social. ‘Treating UUIDs as 128-bit words’ is not what the rest of us object to; it’s doing arbitrary bit frobbing on them and calling the result a UUID that’s confusing, because you’re left holding something that doesn’t satisfy the published definition of a UUID.

If your intent in writing and publishing this library is at least in part so that other people will derive benefit from it, you should (‘should’ not in any abstract moral sense, but in the sense of making it more likely for you to achieve said goal) consider this all as early feedback on how potential users would evaluate your design, and perhaps adapt your design accordingly.

Again, I’m not saying to stop using UUIDs as 128-bit words. But your pedantic users—the kind who would never ask for a Kleenex when they need a facial tissue, or say they’re googling something as they type duckduckgo.com into their browser—won’t appreciate you calling the result a UUID. And if you think the Haskell community has any shortage of pedantic users… heh, how long did you say you’ve been doing this again?

2 Likes

haha oh I’m aware :grin: and that’s why I want to make a library (uuid-typed) that cranks it to 11 on that end of the UUID design spectrum as well!

To get all the instances people do for the UUID type?

I mean as a choice within a program’s architecture, not as an implementation.