Haskell:"实例(Enum a,Bounded a)=>随机a"和"=>任意a"

mis*_*bee 16 random haskell

在Haskell中,是否有用于生成Random/ Arbitrary枚举的"标准"库/包?

我写了下面的代码,但我不敢相信我是第一个有这个需求或解决它的人(而且我不确定我的解决方案是完全正确的).此外,我希望现有的解决方案还有其他不错的功能.

这是一对从Enum类型中选择随机值的函数:

enumRandomR :: (RandomGen g, Enum e) => (e, e) -> g -> (e, g)
enumRandomR  (lo,hi) gen = 
    let (int, gen') = randomR (fromEnum lo, fromEnum hi) gen in (toEnum int, gen')

enumRandom  :: (RandomGen g, Enum e) => g -> (e, g)
enumRandom gen = 
    let (int, gen') = random gen in (toEnum int, gen')
Run Code Online (Sandbox Code Playgroud)

这里是实例System.Random.RandomTest.QuickCheck.Arbitrary

{-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances #-}

instance (Enum a, Bounded a) => Random a where
   random = enumRandom
   randomR = enumRandomR

instance (Enum a, Bounded a) => Arbitrary a where
  arbitrary = choose (minBound, maxBound)
Run Code Online (Sandbox Code Playgroud)

这是一个例子Bounded,Enum类型

data Dir = N | E | S | W
   deriving (Show, Enum, Bounded)
Run Code Online (Sandbox Code Playgroud)

这是对随机/任意方法的测试

> import Test.QuickCheck
> sample (arbitrary:: Gen Dir)
N
E
N
S
N
E
W
N
N
W
W
Run Code Online (Sandbox Code Playgroud)

我很高兴我的解决方案依赖于这些扩展:

{-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances #-}"
Run Code Online (Sandbox Code Playgroud)

因为:

- Constraint is no smaller than the instance head
  in the constraint: Enum a
(Use -XUndecidableInstances to permit this)
Run Code Online (Sandbox Code Playgroud)

,

- Overlapping instances for Random Int
  arising from a use of `randomR'
Matching instances:
  instance Random Int -- Defined in System.Random
  instance (Enum a, Bounded a) => Random a
Run Code Online (Sandbox Code Playgroud)

,和

- Illegal instance declaration for `Random a'
  (All instance types must be of the form (T a1 ... an)
   where a1 ... an are *distinct type variables*,
   and each type variable appears at most once in the instance head.
   Use -XFlexibleInstances if you want to disable this.)
Run Code Online (Sandbox Code Playgroud)

有没有更好的办法?对于某些(更"异国情调")有界枚举类型,我的解决方案是否因为我的简单示例而失败?

ham*_*mar 10

这种情况下的标准解决方法是创建一个newtype包装器并为其提供实例.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}  -- avoid some boilerplate

newtype Enum' a = Enum' a
  deriving (Bounded, Enum, Show)

instance (Enum a, Bounded a) => Random (Enum' a) where
  random = enumRandom
  randomR = enumRandomR

instance (Enum a, Bounded a) => Arbitrary (Enum' a) where
  arbitrary = choose (minBound, maxBound)
Run Code Online (Sandbox Code Playgroud)

当然,这种方法在使用新类型时需要一些额外的包装和展开,但是与QuickCheck一起使用时,这应该不会太糟糕,因为您通常只需要为每个属性进行一次匹配模式:

prop_foo (Enum' x) = ... -- use x as before here
Run Code Online (Sandbox Code Playgroud)

  • @misterbee:是的,我正在使用问题中的定义.这种技术不需要扩展(我只是使用`GeneralizedNewtypeDeriving`为我生成实例;你总是可以自己编写这些实例).至于扩展,`FlexibleInstances`是安全的,而且UndecidableInstances`最糟糕的事情就是如果你像`实例Arbitrary a => Enum a`那样写一些愚蠢的东西,那么无限制地使类型检查器循环.`OverlappingInstances`有点麻烦,但仅在编译时.直到你进入`IncoherentInstances`,你才能在运行时遇到麻烦. (2认同)

Nor*_*sey 10

QuickCheck导出一个函数

arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a
Run Code Online (Sandbox Code Playgroud)

该功能可以合理地被认为是"标准的".


dfl*_*str 7

为任何Enum类型声明这样的实例是不安全的.原因toEnum . fromEnum是不能保证表现得像id.以Enum实例Double为例; 该fromEnum函数只返回double的"截断"整数值.这些"更具异国情调"的类型(如您所说)将无法使用您的解决方案.

这就是为什么通常明智地Random为具体类型创建实例,并完全避免这样的一般声明.

如果您确实要声明所声明的实例,则必须要求您列出的扩展名,因为它是实例声明本身的签名,需要它们.


iva*_*anm 6

不使您的实例"普遍"的另一个原因:想要更频繁地反映"真实世界"值的人,因此想要一个Arbitrary具有不同权重的自定义实例.

(也就是说,我已经使用并定义了一个辅助函数,用于Arbitrary在我自己的代码中编写该实例,以避免为每一个小类型重复它.)

  • @misterbee我不喜欢使用`OverlappingInstances`的东西,因为它对我来说似乎有点脆弱; 最好不要依赖这样的功能恕我直言. (2认同)