Move to Generic.Random namespace

This commit is contained in:
lyxia 2016-08-12 17:42:16 +02:00
parent 0785d1f84e
commit 521ede2c54
16 changed files with 89 additions and 97 deletions

View File

@ -7,7 +7,7 @@ Define sized random generators for almost any type.
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Data
import Test.QuickCheck
import Data.Random.Generics
import Generic.Random.Data
data Term = Lambda Int Term | App Term Term | Var Int
deriving (Show, Data)

View File

@ -14,9 +14,9 @@ import Test.QuickCheck
import Test.QuickCheck.Gen
import Test.QuickCheck.Random
import Control.Exception ( evaluate )
import Data.Random.Generics
import Data.Random.Generics.Internal
import Data.Random.Generics.Internal.Types
import Generic.Random.Data
import Generic.Random.Internal.Data
import Generic.Random.Internal.Types
data T = N T T | L
deriving (Eq, Ord, Show, Data, Generic)

View File

@ -6,7 +6,7 @@ import qualified Data.Vector as Vector
import Data.Text ( Text )
import qualified Data.Text as Text
import Test.QuickCheck
import Data.Random.Generics
import Generic.Random.Data
instance Arbitrary Value where
arbitrary = sized $ generatorPWith aliases

View File

@ -4,9 +4,9 @@
--
-- We generate a list of @Arbitrary@ functions.
import Data.Random.Generics
import Data.Data
import Test.QuickCheck
import Generic.Random.Data
-- | A wrapper for a dummy @Data@ instance.
newtype F = F (Bool -> Bool)

View File

@ -1,7 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
import Test.QuickCheck
import Data.Data
import Data.Random.Generics
import Generic.Random.Data
data Term = Lambda Int Term | App Term Term | Var Int
deriving (Show, Data)

View File

@ -4,8 +4,8 @@
-- The alias wraps a user-defined generator for @Int@ values.
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Random.Generics
import Control.Monad.Random
import Generic.Random.Data
gen :: IO [Int]
gen = asMonadRandom $ generatorPWith aliases 20

View File

@ -2,7 +2,7 @@ import qualified Data.Text as Text
import qualified Data.Text.Lazy.IO as Text
import Test.QuickCheck
import Text.XML
import Data.Random.Generics
import Generic.Random.Data
instance Arbitrary Document where
arbitrary = sized $ generatorSRWith [textAlias] . (4 *)

View File

@ -12,17 +12,18 @@ category: Generics, Testing
build-type: Simple
extra-source-files: README.md
cabal-version: >=1.10
tested-with: GHC == 7.10.3
tested-with: GHC == 8.0.1
library
hs-source-dirs: src
exposed-modules:
Data.Random.Generics
Data.Random.Generics.Internal
Data.Random.Generics.Internal.Boltzmann
Data.Random.Generics.Internal.Oracle
Data.Random.Generics.Internal.Solver
Data.Random.Generics.Internal.Types
Generic.Random.Boltzmann
Generic.Random.Data
Generic.Random.Internal.Common
Generic.Random.Internal.Data
Generic.Random.Internal.Oracle
Generic.Random.Internal.Solver
Generic.Random.Internal.Types
build-depends:
base >= 4.8 && < 5,
containers,

View File

@ -1,8 +1,8 @@
-- | Applicative framework to define recursive structures and derive Boltzmann
-- | Applicative interface to define recursive structures and derive Boltzmann
-- samplers.
--
-- Given the recursive structure of the types, and how to combine generators,
-- the framework takes care of computing the oracles and setting the right
-- the library takes care of computing the oracles and setting the right
-- distributions.
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs, RankNTypes, ScopedTypeVariables #-}
@ -10,7 +10,7 @@
{-# LANGUAGE RecordWildCards, DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies, MultiParamTypeClasses #-}
{-# LANGUAGE TypeApplications #-}
module Data.Random.Generics.Internal.Boltzmann where
module Generic.Random.Boltzmann where
import Control.Applicative
import Control.Monad
@ -23,8 +23,9 @@ import Data.List.Split
import Data.Vector ( Vector )
import qualified Data.Vector as V
import qualified Numeric.AD as AD
import Data.Random.Generics.Internal.Solver
import Data.Random.Generics.Internal.Types
import Generic.Random.Internal.Common
import Generic.Random.Internal.Solver
import Generic.Random.Internal.Types
class Embed f m where
emap :: (m a -> m b) -> f a -> f b
@ -161,24 +162,3 @@ point k s = System ((k + 1) * dim s) $ \x ->
where
flatten = join . fmap (V.fromList . take (k + 1) . unPointiful)
resize = V.fromList . fmap Pointiful . chunksOf (k + 1) . V.toList
frequencyWith
:: (Ord r, Num r, Monad m) => (r -> m r) -> [(r, m a)] -> m a
frequencyWith _ [(_, a)] = a
frequencyWith randomR as = randomR total >>= select as
where
total = (sum . fmap fst) as
select ((w, a) : as) x
| x < w = a
| otherwise = select as (x - w)
select _ _ = (snd . head) as
-- That should not happen in theory, but floating point might be funny.
-- | Binomial coefficient.
--
-- > binomial n k == factorial n `div` (factorial k * factorial (n-k))
binomial :: Int -> Int -> Integer
binomial = \n k -> pascal !! n !! k
where
pascal = [1] : fmap nextRow pascal
nextRow r = zipWith (+) (0 : r) (r ++ [0])

View File

@ -23,7 +23,7 @@
-- When these functions are specialized, oracles are memoized and will be
-- reused for different sizes.
module Data.Random.Generics (
module Generic.Random.Data (
Size',
-- * Main functions
-- $sized
@ -69,8 +69,8 @@ module Data.Random.Generics (
) where
import Data.Data
import Data.Random.Generics.Internal
import Data.Random.Generics.Internal.Types
import Generic.Random.Internal.Data
import Generic.Random.Internal.Types
-- * Main functions
@ -215,7 +215,7 @@ generator' = generatorWith' []
-- @
--
-- Another use case is to plug in user-defined generators where the default is
-- not satisfactory, for example, to get positive @Int@s:
-- not satisfactory, for example, to generate positive @Int@s:
--
-- @
-- let
@ -223,6 +223,17 @@ generator' = generatorWith' []
-- in
-- 'generatorPWith' as 'asGen' :: 'Size' -> 'Gen' [Int]
-- @
--
-- or to modify the weights assigned to some types. In particular, in some
-- cases it seems preferable to make @String@ (and @Text@) have the same weight
-- as @Int@ and @()@.
--
-- @
-- let
-- as = ['alias' $ \\() -> arbitrary :: 'Gen' String]
-- in
-- 'generatorPWith' as 'asGen' :: 'Size' -> 'Gen' (Either Int String)
-- @
generatorSRWith
:: (Data a, MonadRandomLike m) => [AliasR m] -> Size' -> m a

View File

@ -0,0 +1,39 @@
-- | General helper functions
module Generic.Random.Internal.Common where
frequencyWith
:: (Ord r, Num r, Monad m) => (r -> m r) -> [(r, m a)] -> m a
frequencyWith _ [(_, a)] = a
frequencyWith randomR as = randomR total >>= select as
where
total = (sum . fmap fst) as
select ((w, a) : as) x
| x < w = a
| otherwise = select as (x - w)
select _ _ = (snd . head) as
-- That should not happen in theory, but floating point might be funny.
-- | @partitions k n@: lists of non-negative integers of length @n@ with sum
-- less than or equal to @k@.
partitions :: Int -> Int -> [[Int]]
partitions _ 0 = [[]]
partitions k n = do
p <- [0 .. k]
(p :) <$> partitions (k - p) (n - 1)
-- | Binomial coefficient.
--
-- > binomial n k == factorial n `div` (factorial k * factorial (n-k))
binomial :: Int -> Int -> Integer
binomial = \n k -> pascal !! n !! k
where
pascal = [1] : fmap nextRow pascal
nextRow r = zipWith (+) (0 : r) (r ++ [0])
-- | Multinomial coefficient.
--
-- > multinomial n ps == factorial n `div` product [factorial p | p <- ps]
multinomial :: Int -> [Int] -> Integer
multinomial _ [] = 1
multinomial n (p : ps) = binomial n p * multinomial (n - p) ps

View File

@ -1,5 +1,5 @@
{-# LANGUAGE RecordWildCards, DeriveFunctor #-}
module Data.Random.Generics.Internal where
module Generic.Random.Internal.Data where
import Control.Arrow ( (&&&) )
import Control.Applicative
@ -7,8 +7,8 @@ import Data.Data
import Data.Foldable
import Data.Maybe
import qualified Data.HashMap.Lazy as HashMap
import Data.Random.Generics.Internal.Oracle
import Data.Random.Generics.Internal.Types
import Generic.Random.Internal.Oracle
import Generic.Random.Internal.Types
-- | Sized generator.
data SG r = SG

View File

@ -1,7 +1,7 @@
{-# LANGUAGE FlexibleContexts, GADTs, RankNTypes, ScopedTypeVariables #-}
{-# LANGUAGE DeriveGeneric, ImplicitParams #-}
{-# LANGUAGE RecordWildCards, DeriveDataTypeable #-}
module Data.Random.Generics.Internal.Oracle where
module Generic.Random.Internal.Oracle where
import Control.Applicative
import Control.Monad
@ -18,8 +18,9 @@ import Data.Monoid
import qualified Data.Vector as V
import GHC.Generics ( Generic )
import Numeric.AD
import Data.Random.Generics.Internal.Types
import Data.Random.Generics.Internal.Solver
import Generic.Random.Internal.Common
import Generic.Random.Internal.Solver
import Generic.Random.Internal.Types
-- | We build a dictionary which reifies type information in order to
-- create a Boltzmann generator.
@ -481,58 +482,18 @@ ix (C i _) = i
dd ?! j = C i k
where (k, i) = j `divMod` count dd
getGenerator :: (Functor m, Data a)
=> DataDef m -> Generators m -> proxy a -> Int -> m a
getGenerator :: Data a => DataDef m -> Generators m -> proxy a -> Int -> m a
getGenerator dd (l, r) a k = unSomeData $
case index dd #! typeRep a of
Right i -> (r #! C i k)
Left j -> (l #! AC j k)
getSmallGenerator :: (Functor m, Data a)
=> DataDef m -> SmallGenerators m -> proxy a -> m a
getSmallGenerator :: Data a => DataDef m -> SmallGenerators m -> proxy a -> m a
getSmallGenerator dd (l, r) a = unSomeData $
case index dd #! typeRep a of
Right i -> (r #! i)
Left j -> (l #! j)
-- * General helper functions
frequencyWith
:: (Show r, Ord r, Num r, Monad m) => (r -> m r) -> [(r, m a)] -> m a
frequencyWith _ [(_, a)] = a
frequencyWith randomR as = randomR total >>= select as
where
total = (sum . fmap fst) as
select ((w, a) : as) x
| x < w = a
| otherwise = select as (x - w)
select _ _ = (snd . head) as
-- That should not happen in theory, but floating point might be funny.
(#!) :: (Eq k, Hashable k)
=> HashMap k v -> k -> v
(#!) = (HashMap.!)
-- | @partitions k n@: lists of non-negative integers of length @n@ with sum
-- less than or equal to @k@.
partitions :: Int -> Int -> [[Int]]
partitions _ 0 = [[]]
partitions k n = do
p <- [0 .. k]
(p :) <$> partitions (k - p) (n - 1)
-- | Multinomial coefficient.
--
-- > multinomial n ps == factorial n `div` product [factorial p | p <- ps]
multinomial :: Int -> [Int] -> Integer
multinomial _ [] = 1
multinomial n (p : ps) = binomial n p * multinomial (n - p) ps
-- | Binomial coefficient.
--
-- > binomial n k == factorial n `div` (factorial k * factorial (n-k))
binomial :: Int -> Int -> Integer
binomial = \n k -> pascal !! n !! k
where
pascal = [1] : fmap nextRow pascal
nextRow r = zipWith (+) (0 : r) (r ++ [0])

View File

@ -2,7 +2,7 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE RankNTypes, FlexibleContexts, TypeFamilies #-}
module Data.Random.Generics.Internal.Solver where
module Generic.Random.Internal.Solver where
import Control.Applicative
import Data.AEq ( (~==) )

View File

@ -1,6 +1,6 @@
{-# LANGUAGE RankNTypes, GADTs, ScopedTypeVariables, ImplicitParams #-}
{-# LANGUAGE TypeOperators, GeneralizedNewtypeDeriving #-}
module Data.Random.Generics.Internal.Types where
module Generic.Random.Internal.Types where
import Control.Monad.Random
import Control.Monad.Trans

View File

@ -4,7 +4,7 @@ import Data.Data
import Data.Foldable
import Data.List
import Test.QuickCheck
import Data.Random.Generics
import Generic.Random.Data
data T = N T T | L
deriving (Eq, Ord, Show, Data)