February meetup Thurs 19th - planning

7 views
Skip to first unread message

Ben Hutchison

unread,
Jan 15, 2026, 9:15:19 PM (12 days ago) Jan 15
to Melbourne Compose Group, John Walker
Hi all,

Thanks to everyone who contributed to last night's fun session looking at Lean.

Our next meeting will be Thursday Feb 19th. If anyone has something they want to present, share, talk about or do in Feb, please get in touch with John and/or I.

-Ben

Viktor Dukhovni

unread,
Jan 18, 2026, 10:50:27 PM (9 days ago) Jan 18
to Melbourne Compose Group

On Friday, January 16, 2026 at 1:15:19 PM UTC+11 Ben Hutchison wrote:

Thanks to everyone who contributed to last night's fun session looking at Lean.

My apologies for missing the January meeting, …


Our next meeting will be Thursday Feb 19th. If anyone has something they want to present, share, talk about or do in Feb, please get in touch with John and/or I.

I recently wanted to use Haskell’s unordered-containers with potentially untrusted data, so the natural inclination is to use a salted hash, but the libraries don’t go out of their way to make that obviously easy. I could go over the approach I settled on.

Demo code:

module Main (main) where import Data.Hashable import System.Random (randomIO) import qualified Net.DNSBase.Internal.Salted as SM import Net.DNSBase.Internal.Salted (Salt(..), SaltedMap(..)) import Net.DNSBase.Internal.Salted (withSalt, withSaltedMap) import Net.DNSBase.Internal.Salted (salted, saltedKVL, unsaltedKVL) import Net.DNSBase.Internal.Util main :: IO () main = do salt <- SaltValue <$> randomIO let keys = map fst kvl sm = withSalt salt \ p -> SaltedMap p $ SM.fromList $ saltedKVL kvl withSaltedMap sm \ _ m -> do forM_ keys \ k -> do let sk = salted k v = SM.lookup sk m print (k, hash k, hash sk, v) mapM_ print $ unsaltedKVL $ SM.toList m where kvl :: [(Int, String)] kvl = [(42, "foo"), (1729, "bar")]

Running the demo:

$ cabal run -v0 salt (42,42,-6961275629001087492,Just "foo") (1729,1729,-2624499557206730258,Just "bar") (1729,"bar") (42,"foo") $ cabal run -v0 salt (42,42,-9186782270719650544,Just "foo") (1729,1729,1500759628826157619,Just "bar") (42,"foo") (1729,"bar")

The underlying module (various extensions are implicit via the .cabal file):

module Net.DNSBase.Internal.Salted ( Salt(.., SaltValue) , withSalt , salted , unsalted , saltedKVL , unsaltedKVL , SaltedMap(..) , withSaltedMap , module Data.Hashable , module Data.HashMap.Strict ) where import Data.Hashable (Hashable, hashWithSalt, hash) import Data.HashMap.Strict import Net.DNSBase.Internal.Util -- | Existentially encoded reified 'Int' proxy. data Salt where Salt :: forall (s :: Type) (p :: Type -> Type). Reifies s Int => p s -> Salt -- | Construct or destruct 'Salt' values. pattern SaltValue :: Int -> Salt pattern SaltValue i <- (shake -> i) where SaltValue i = reify i Salt -- | Evaluate an expression that needs reified salt. withSalt :: forall (r :: Type). Salt -> (forall (s :: Type) (p :: Type -> Type). Reifies s Int => p s -> r) -> r withSalt (Salt p) f = f p {-# INLINE withSalt #-} shake :: Salt -> Int shake s = withSalt s reflect {-# INLINE shake #-} -- | Apply type-level salt to a type type Salted :: Type -> Type -> Type newtype Salted s k = Salted k deriving newtype (Eq, Show) instance (Reifies s Int, Hashable k) => Hashable (Salted s k) where hashWithSalt t k = hashWithSalt (t + reflect (Proxy @s)) (unsalted k) {-# INLINE hashWithSalt #-} -- | Coerce to salted. salted :: forall s k. k -> Salted s k salted = coerce {-# INLINE salted #-} -- | Coerce from salted. unsalted :: forall s k. Salted s k -> k unsalted = coerce {-# INLINE unsalted #-} -- | Coerce a (key, value) list to one with salted keys. saltedKVL :: forall s k (v :: Type). [(k, v)] -> [(Salted s k, v)] saltedKVL = coerce {-# INLINE saltedKVL #-} -- | Coerce a (salted key, value) list to one with plain keys. unsaltedKVL :: forall s k (v :: Type). [(Salted s k, v)] -> [(k, v)] unsaltedKVL = coerce {-# INLINE unsaltedKVL #-} -- | Ordinary 'HashMap' with salted keys. type SHM :: Type -> Type -> Type -> Type type SHM s k v = HashMap (Salted s k) v -- | Existentially wrapped relified salt and associated 'HashMap'. type SaltedMap :: Type -> Type -> Type data SaltedMap k v where SaltedMap :: forall s k v p. Reifies s Int => p s -> SHM s k v -> SaltedMap k v withSaltedMap :: SaltedMap k v -> (forall s p. Reifies s Int => p s -> SHM s k v -> r) -> r withSaltedMap (SaltedMap p m) f = f p m {-# INLINE withSaltedMap #-}

Ben Hutchison

unread,
Jan 20, 2026, 8:12:41 PM (7 days ago) Jan 20
to Viktor Dukhovni, Melbourne Compose Group
We love a meaty topic Viktor, and if it's salted, all the better ;)

John's been missing the sight of cool, calm and collected Haskell code on his eyeballs, so I'm sure this topic will delight.

I'll make a Luma event draft and run the topic description by you before scheduling.

-Ben

--
You received this message because you are subscribed to the Google Groups "Melbourne Compose Group" group.
To unsubscribe from this group and stop receiving emails from it, send an email to melbourne-compose...@googlegroups.com.
To view this discussion, visit https://groups.google.com/d/msgid/melbourne-compose-group/0caf7902-63d5-4df5-ae8c-b2aea6dfe2d8n%40googlegroups.com.
Reply all
Reply to author
Forward
0 new messages