以下代码使用不安全的GeneralizedNewtypeDeriving
扩展程序通过插入具有不同Data.Set
个实例的不同元素来中断Ord
:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Data.Set
import System.Random
class AlaInt i where
fromIntSet :: Set Integer -> Set i
toIntSet :: Set i -> Set Integer
instance AlaInt Integer where
fromIntSet = id
toIntSet = id
newtype I = I Integer deriving (Eq, Show, AlaInt)
instance Ord I where compare (I n1) (I n2) = compare n2 n1 -- sic!
insert' :: Integer -> Set Integer -> Set Integer
insert' n s = toIntSet $ insert (I n) $ fromIntSet s
randomInput = take 5000 $ zip (randomRs (0,9) gen) (randoms gen) where
gen = mkStdGen 911
createSet = Prelude.foldr f empty where
f (e,True) = insert e
f (e,False) = insert' e
main = print $ toAscList $ createSet randomInput
代码打印[1,3,5,7,8,6,9,6,4,2,0,9]
。请注意,该列表是无序的,并且9
两次。
是否可以使用其他扩展程序执行此字典交换攻击,例如ConstraintKinds
?如果是,可以Data.Set
重新设计以适应此类攻击吗?
答案 0 :(得分:20)
我认为这是一个重要的问题,所以我将从其他地方重复我的回答:你可以在Haskell98中为同一类型创建同一类的多个实例,而不需要任何扩展:
$ cat A.hs
module A where
data U = X | Y deriving (Eq, Show)
$ cat B.hs
module B where
import Data.Set
import A
instance Ord U where
compare X X = EQ
compare X Y = LT
compare Y X = GT
compare Y Y = EQ
ins :: U -> Set U -> Set U
ins = insert
$ cat C.hs
module C where
import Data.Set
import A
instance Ord U where
compare X X = EQ
compare X Y = GT
compare Y X = LT
compare Y Y = EQ
ins' :: U -> Set U -> Set U
ins' = insert
$ cat D.hs
module D where
import Data.Set
import A
import B
import C
test = ins' X $ ins X $ ins Y $ empty
$ ghci D.hs
Prelude D> test
fromList [X,Y,X]
是的,您可以通过在内部存储字典来阻止此类攻击:
data MSet a where MSet :: Ord a => Set a -> MSet a