{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE RankNTypes #-}
module Verismith.Verilog2005.Generator
( runGarbageGeneration,
GarbageOpts,
GenM,
defGarbageOpts,
)
where
import Control.Applicative (liftA2, liftA3)
import Data.Functor.Compose
import Control.Lens hiding ((<.>))
import Control.Monad (join, replicateM)
import Control.Monad.Reader
import Control.Monad.State.Lazy
import qualified Data.ByteString as B
import Data.ByteString.Internal (c2w, w2c)
import qualified Data.IntMap.Strict as IntMap
import Data.List.NonEmpty (NonEmpty (..), toList)
import qualified Data.List.NonEmpty as NE
import Data.Tuple
import qualified Data.Vector.Unboxed as VU
import Numeric.Natural
import System.Random.MWC.Probability
import Verismith.Config
import Verismith.Utils (mkpair)
import Verismith.Verilog2005.AST
import Verismith.Verilog2005.Lexer
import Verismith.Verilog2005.Randomness
infixl 4 <.>
(<.>) :: (Monad m, Applicative m) => m (a -> m b) -> m a -> m b
<.> :: forall (m :: * -> *) a b.
(Monad m, Applicative m) =>
m (a -> m b) -> m a -> m b
(<.>) m (a -> m b)
mf m a
mx = m (m b) -> m b
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (m (m b) -> m b) -> m (m b) -> m b
forall a b. (a -> b) -> a -> b
$ m (a -> m b)
mf m (a -> m b) -> m a -> m (m b)
forall a b. m (a -> b) -> m a -> m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> m a
mx
attenuateCat :: (NonEmpty (Bool, a)) -> Double -> CategoricalProbability -> CategoricalProbability
attenuateCat :: forall a.
NonEmpty (Bool, a)
-> Double -> CategoricalProbability -> CategoricalProbability
attenuateCat NonEmpty (Bool, a)
l Double
d CategoricalProbability
p = case CategoricalProbability
p of
CPDiscrete NonEmpty Double
wl -> NonEmpty Double -> CategoricalProbability
CPDiscrete (NonEmpty Double -> CategoricalProbability)
-> NonEmpty Double -> CategoricalProbability
forall a b. (a -> b) -> a -> b
$ ((Bool, a) -> Double -> Double)
-> NonEmpty (Bool, a) -> NonEmpty Double -> NonEmpty Double
forall a b c.
(a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
NE.zipWith (\(Bool, a)
a Double
w -> Double
w Double -> Double -> Double
forall a. Num a => a -> a -> a
* if (Bool, a) -> Bool
forall a b. (a, b) -> a
fst (Bool, a)
a then Double
d else Double
1) NonEmpty (Bool, a)
l NonEmpty Double
wl
CPBiasedUniform [(Double, Int)]
wl Double
wb ->
let im :: IntMap Double
im = (Double -> Double -> Double) -> [(Int, Double)] -> IntMap Double
forall a. (a -> a -> a) -> [(Int, a)] -> IntMap a
IntMap.fromListWith Double -> Double -> Double
forall a. Num a => a -> a -> a
(+) ([(Int, Double)] -> IntMap Double)
-> [(Int, Double)] -> IntMap Double
forall a b. (a -> b) -> a -> b
$ ((Double, Int) -> (Int, Double))
-> [(Double, Int)] -> [(Int, Double)]
forall a b. (a -> b) -> [a] -> [b]
map (Double, Int) -> (Int, Double)
forall a b. (a, b) -> (b, a)
swap [(Double, Int)]
wl
in NonEmpty Double -> CategoricalProbability
CPDiscrete (NonEmpty Double -> CategoricalProbability)
-> NonEmpty Double -> CategoricalProbability
forall a b. (a -> b) -> a -> b
$
((Int, (Bool, a)) -> Double)
-> NonEmpty (Int, (Bool, a)) -> NonEmpty Double
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map (\(Int
k, (Bool, a)
a) -> Double -> Int -> IntMap Double -> Double
forall a. a -> Int -> IntMap a -> a
IntMap.findWithDefault Double
wb Int
k IntMap Double
im Double -> Double -> Double
forall a. Num a => a -> a -> a
* if (Bool, a) -> Bool
forall a b. (a, b) -> a
fst (Bool, a)
a then Double
d else Double
1) (NonEmpty (Int, (Bool, a)) -> NonEmpty Double)
-> NonEmpty (Int, (Bool, a)) -> NonEmpty Double
forall a b. (a -> b) -> a -> b
$
NonEmpty Int -> NonEmpty (Bool, a) -> NonEmpty (Int, (Bool, a))
forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
NE.zip [Int
Item (NonEmpty Int)
0..] NonEmpty (Bool, a)
l
attenuateNum :: Double -> NumberProbability -> NumberProbability
attenuateNum :: Double -> NumberProbability -> NumberProbability
attenuateNum Double
d NumberProbability
p =
if Double
d Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
1
then NumberProbability
p
else case NumberProbability
p of
NPUniform Int
l Int
h ->
NonEmpty (Double, Int) -> NumberProbability
NPDiscrete (NonEmpty (Double, Int) -> NumberProbability)
-> NonEmpty (Double, Int) -> NumberProbability
forall a b. (a -> b) -> a -> b
$
if Double
d Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 then [(Double
1, Int
l)] else [(Double, Int)] -> NonEmpty (Double, Int)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList ((Double -> Int -> (Double, Int))
-> [Double] -> [Int] -> [(Double, Int)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Double -> Int -> (Double, Int)
forall {b}. Integral b => Double -> b -> (Double, b)
mkdistrfor [Double
Item [Double]
1 ..] [Int
Item [Int]
l .. Int
Item [Int]
h])
NPBinomial Int
off Int
t Double
p ->
if Double
d Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0
then NonEmpty (Double, Int) -> NumberProbability
NPDiscrete [(Double
1, Int
off)]
else Int -> Int -> Double -> NumberProbability
NPBinomial Int
off Int
t (Double -> NumberProbability) -> Double -> NumberProbability
forall a b. (a -> b) -> a -> b
$ Double
p Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
d
NPNegativeBinomial Int
off Double
pf Int
f ->
if Double
d Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0
then NonEmpty (Double, Int) -> NumberProbability
NPDiscrete [(Double
1, Int
off)]
else Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
off (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- (Double
1 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
pf) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
d) Int
f
NPPoisson Int
off Double
p ->
if Double
d Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0
then NonEmpty (Double, Int) -> NumberProbability
NPDiscrete [(Double
1, Int
off)]
else Int -> Double -> NumberProbability
NPPoisson Int
off (Double -> NumberProbability) -> Double -> NumberProbability
forall a b. (a -> b) -> a -> b
$ Double
p Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
d
NPDiscrete NonEmpty (Double, Int)
l -> NonEmpty (Double, Int) -> NumberProbability
NPDiscrete (NonEmpty (Double, Int) -> NumberProbability)
-> NonEmpty (Double, Int) -> NumberProbability
forall a b. (a -> b) -> a -> b
$ if Double
d Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0 then [NonEmpty (Double, Int) -> (Double, Int)
forall a. NonEmpty a -> a
NE.head NonEmpty (Double, Int)
l] else ((Double, Int) -> (Double, Int))
-> NonEmpty (Double, Int) -> NonEmpty (Double, Int)
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map ((Double -> Int -> (Double, Int)) -> (Double, Int) -> (Double, Int)
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Double -> Int -> (Double, Int)
forall {b}. Integral b => Double -> b -> (Double, b)
mkdistrfor) NonEmpty (Double, Int)
l
NPLinearComb NonEmpty (Double, NumberProbability)
l -> NonEmpty (Double, NumberProbability) -> NumberProbability
NPLinearComb (NonEmpty (Double, NumberProbability) -> NumberProbability)
-> NonEmpty (Double, NumberProbability) -> NumberProbability
forall a b. (a -> b) -> a -> b
$ ((Double, NumberProbability) -> (Double, NumberProbability))
-> NonEmpty (Double, NumberProbability)
-> NonEmpty (Double, NumberProbability)
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map (\(Double
p, NumberProbability
np) -> (Double
p, Double -> NumberProbability -> NumberProbability
attenuateNum Double
d NumberProbability
np)) NonEmpty (Double, NumberProbability)
l
where
mkdistrfor :: Double -> b -> (Double, b)
mkdistrfor Double
bw b
n = (Double
bw Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
d Double -> Double -> Double
forall a. Floating a => a -> a -> a
** b -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral b
n, b
n)
type GenM' = GenM GarbageOpts
applyAttenuation :: Int -> GarbageAttenuationOpts -> GarbageAttenuationOpts
applyAttenuation :: Int -> GarbageAttenuationOpts -> GarbageAttenuationOpts
applyAttenuation Int
n GarbageAttenuationOpts
x = GarbageAttenuationOpts
x GarbageAttenuationOpts
-> (GarbageAttenuationOpts -> GarbageAttenuationOpts)
-> GarbageAttenuationOpts
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double)
-> GarbageAttenuationOpts -> Identity GarbageAttenuationOpts
Lens' GarbageAttenuationOpts Double
gaoCurrent ((Double -> Identity Double)
-> GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> Double -> GarbageAttenuationOpts -> GarbageAttenuationOpts
forall a s t. Num a => ASetter s t a a -> a -> s -> t
*~ GarbageAttenuationOpts -> Double
_gaoDecrease GarbageAttenuationOpts
x Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n
tameExprRecursion :: Int -> GenM' a -> GenM' a
tameExprRecursion :: forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
n = ((GarbageOpts, Gen RealWorld) -> (GarbageOpts, Gen RealWorld))
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall a.
((GarbageOpts, Gen RealWorld) -> (GarbageOpts, Gen RealWorld))
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local ((GarbageOpts -> Identity GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld)
forall s t a b. Field1 s t a b => Lens s t a b
Lens
(GarbageOpts, Gen RealWorld)
(GarbageOpts, Gen RealWorld)
GarbageOpts
GarbageOpts
_1 ((GarbageOpts -> Identity GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld))
-> ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageOpts -> Identity GarbageOpts)
-> (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageExprOpts -> Identity GarbageExprOpts)
-> GarbageOpts -> Identity GarbageOpts
Lens' GarbageOpts GarbageExprOpts
goExpr ((GarbageExprOpts -> Identity GarbageExprOpts)
-> GarbageOpts -> Identity GarbageOpts)
-> ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageExprOpts -> Identity GarbageExprOpts)
-> (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageOpts
-> Identity GarbageOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageExprOpts -> Identity GarbageExprOpts
Lens' GarbageExprOpts GarbageAttenuationOpts
geoAttenuation ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld))
-> (GarbageAttenuationOpts -> GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> (GarbageOpts, Gen RealWorld)
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Int -> GarbageAttenuationOpts -> GarbageAttenuationOpts
applyAttenuation Int
n)
repeatExprRecursive :: (GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive :: forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive GarbageOpts -> NumberProbability
p GenM' a
m = do
Int
n <- (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum (GarbageExprOpts -> GarbageAttenuationOpts
_geoAttenuation (GarbageExprOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> GarbageExprOpts)
-> GarbageOpts
-> GarbageAttenuationOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr) GarbageOpts -> NumberProbability
p
Int -> GenM' [a] -> GenM' [a]
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
n (GenM' [a] -> GenM' [a]) -> GenM' [a] -> GenM' [a]
forall a b. (a -> b) -> a -> b
$ Int -> GenM' a -> GenM' [a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n GenM' a
m
tameStmtRecursion :: Int -> GenM' a -> GenM' a
tameStmtRecursion :: forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
n = ((GarbageOpts, Gen RealWorld) -> (GarbageOpts, Gen RealWorld))
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall a.
((GarbageOpts, Gen RealWorld) -> (GarbageOpts, Gen RealWorld))
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local ((GarbageOpts -> Identity GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld)
forall s t a b. Field1 s t a b => Lens s t a b
Lens
(GarbageOpts, Gen RealWorld)
(GarbageOpts, Gen RealWorld)
GarbageOpts
GarbageOpts
_1 ((GarbageOpts -> Identity GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld))
-> ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageOpts -> Identity GarbageOpts)
-> (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageStatementOpts -> Identity GarbageStatementOpts)
-> GarbageOpts -> Identity GarbageOpts
Lens' GarbageOpts GarbageStatementOpts
goStatement ((GarbageStatementOpts -> Identity GarbageStatementOpts)
-> GarbageOpts -> Identity GarbageOpts)
-> ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageStatementOpts -> Identity GarbageStatementOpts)
-> (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageOpts
-> Identity GarbageOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageStatementOpts -> Identity GarbageStatementOpts
Lens' GarbageStatementOpts GarbageAttenuationOpts
gstoAttenuation ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld))
-> (GarbageAttenuationOpts -> GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> (GarbageOpts, Gen RealWorld)
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Int -> GarbageAttenuationOpts -> GarbageAttenuationOpts
applyAttenuation Int
n)
repeatStmtRecursive :: (GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatStmtRecursive :: forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatStmtRecursive GarbageOpts -> NumberProbability
p GenM' a
m = do
Int
n <- (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum (GarbageStatementOpts -> GarbageAttenuationOpts
_gstoAttenuation (GarbageStatementOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> GarbageStatementOpts)
-> GarbageOpts
-> GarbageAttenuationOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement) GarbageOpts -> NumberProbability
p
Int -> GenM' [a] -> GenM' [a]
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
n (GenM' [a] -> GenM' [a]) -> GenM' [a] -> GenM' [a]
forall a b. (a -> b) -> a -> b
$ Int -> GenM' a -> GenM' [a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n GenM' a
m
tameModGenRecursion :: Int -> GenM' a -> GenM' a
tameModGenRecursion :: forall a. Int -> GenM' a -> GenM' a
tameModGenRecursion Int
n = ((GarbageOpts, Gen RealWorld) -> (GarbageOpts, Gen RealWorld))
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall a.
((GarbageOpts, Gen RealWorld) -> (GarbageOpts, Gen RealWorld))
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
local ((GarbageOpts -> Identity GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld)
forall s t a b. Field1 s t a b => Lens s t a b
Lens
(GarbageOpts, Gen RealWorld)
(GarbageOpts, Gen RealWorld)
GarbageOpts
GarbageOpts
_1 ((GarbageOpts -> Identity GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld))
-> ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageOpts -> Identity GarbageOpts)
-> (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageGenerateOpts -> Identity GarbageGenerateOpts)
-> GarbageOpts -> Identity GarbageOpts
Lens' GarbageOpts GarbageGenerateOpts
goGenerate ((GarbageGenerateOpts -> Identity GarbageGenerateOpts)
-> GarbageOpts -> Identity GarbageOpts)
-> ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageGenerateOpts -> Identity GarbageGenerateOpts)
-> (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageOpts
-> Identity GarbageOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> GarbageGenerateOpts -> Identity GarbageGenerateOpts
Lens' GarbageGenerateOpts GarbageAttenuationOpts
ggoAttenuation ((GarbageAttenuationOpts -> Identity GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Identity (GarbageOpts, Gen RealWorld))
-> (GarbageAttenuationOpts -> GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> (GarbageOpts, Gen RealWorld)
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Int -> GarbageAttenuationOpts -> GarbageAttenuationOpts
applyAttenuation Int
n)
repeatModGenRecursive :: (GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatModGenRecursive :: forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatModGenRecursive GarbageOpts -> NumberProbability
p GenM' a
m = do
Int
n <- (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum (GarbageGenerateOpts -> GarbageAttenuationOpts
_ggoAttenuation (GarbageGenerateOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> GarbageGenerateOpts)
-> GarbageOpts
-> GarbageAttenuationOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate) GarbageOpts -> NumberProbability
p
Int -> GenM' [a] -> GenM' [a]
forall a. Int -> GenM' a -> GenM' a
tameModGenRecursion Int
n (GenM' [a] -> GenM' [a]) -> GenM' [a] -> GenM' [a]
forall a b. (a -> b) -> a -> b
$ Int -> GenM' a -> GenM' [a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n GenM' a
m
sampleAttenuatedBranch ::
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> (NonEmpty (Bool, GenM' a))
-> GenM' a
sampleAttenuatedBranch :: forall a.
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' a)
-> GenM' a
sampleAttenuatedBranch GarbageOpts -> GarbageAttenuationOpts
f GarbageOpts -> CategoricalProbability
p NonEmpty (Bool, GenM' a)
l = do
Gen RealWorld
gen <- ((GarbageOpts, Gen RealWorld) -> Gen RealWorld)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Gen RealWorld)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (GarbageOpts, Gen RealWorld) -> Gen RealWorld
forall a b. (a, b) -> b
snd
CategoricalProbability
d <- ((GarbageOpts, Gen RealWorld) -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO CategoricalProbability
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (((GarbageOpts, Gen RealWorld) -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO CategoricalProbability)
-> ((GarbageOpts, Gen RealWorld) -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO CategoricalProbability
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> CategoricalProbability
p (GarbageOpts -> CategoricalProbability)
-> ((GarbageOpts, Gen RealWorld) -> GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> CategoricalProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageOpts, Gen RealWorld) -> GarbageOpts
forall a b. (a, b) -> a
fst
Double
a <- ((GarbageOpts, Gen RealWorld) -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Double
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (((GarbageOpts, Gen RealWorld) -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Double)
-> ((GarbageOpts, Gen RealWorld) -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Double
forall a b. (a -> b) -> a -> b
$ GarbageAttenuationOpts -> Double
_gaoCurrent (GarbageAttenuationOpts -> Double)
-> ((GarbageOpts, Gen RealWorld) -> GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageAttenuationOpts
f (GarbageOpts -> GarbageAttenuationOpts)
-> ((GarbageOpts, Gen RealWorld) -> GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> GarbageAttenuationOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageOpts, Gen RealWorld) -> GarbageOpts
forall a b. (a, b) -> a
fst
ReaderT (GarbageOpts, Gen RealWorld) IO (GenM' a) -> GenM' a
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (ReaderT (GarbageOpts, Gen RealWorld) IO (GenM' a) -> GenM' a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenM' a) -> GenM' a
forall a b. (a -> b) -> a -> b
$ [GenM' a]
-> Gen (PrimState (ReaderT (GarbageOpts, Gen RealWorld) IO))
-> CategoricalProbability
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenM' a)
forall (m :: * -> *) a.
(Functor m, PrimMonad m) =>
[a] -> Gen (PrimState m) -> CategoricalProbability -> m a
sampleIn (NonEmpty (GenM' a) -> [GenM' a]
forall a. NonEmpty a -> [a]
toList (NonEmpty (GenM' a) -> [GenM' a])
-> NonEmpty (GenM' a) -> [GenM' a]
forall a b. (a -> b) -> a -> b
$ ((Bool, GenM' a) -> GenM' a)
-> NonEmpty (Bool, GenM' a) -> NonEmpty (GenM' a)
forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
NE.map (Bool, GenM' a) -> GenM' a
forall a b. (a, b) -> b
snd NonEmpty (Bool, GenM' a)
l) Gen RealWorld
Gen (PrimState (ReaderT (GarbageOpts, Gen RealWorld) IO))
gen (NonEmpty (Bool, GenM' a)
-> Double -> CategoricalProbability -> CategoricalProbability
forall a.
NonEmpty (Bool, a)
-> Double -> CategoricalProbability -> CategoricalProbability
attenuateCat NonEmpty (Bool, GenM' a)
l Double
a CategoricalProbability
d)
sampleAttenuatedNum ::
(GarbageOpts -> GarbageAttenuationOpts) -> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum :: (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum GarbageOpts -> GarbageAttenuationOpts
f GarbageOpts -> NumberProbability
p = do
Gen RealWorld
gen <- ((GarbageOpts, Gen RealWorld) -> Gen RealWorld)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Gen RealWorld)
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (GarbageOpts, Gen RealWorld) -> Gen RealWorld
forall a b. (a, b) -> b
snd
NumberProbability
d <- ((GarbageOpts, Gen RealWorld) -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NumberProbability
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (((GarbageOpts, Gen RealWorld) -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NumberProbability)
-> ((GarbageOpts, Gen RealWorld) -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NumberProbability
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> NumberProbability
p (GarbageOpts -> NumberProbability)
-> ((GarbageOpts, Gen RealWorld) -> GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageOpts, Gen RealWorld) -> GarbageOpts
forall a b. (a, b) -> a
fst
Double
a <- ((GarbageOpts, Gen RealWorld) -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Double
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (((GarbageOpts, Gen RealWorld) -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Double)
-> ((GarbageOpts, Gen RealWorld) -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Double
forall a b. (a -> b) -> a -> b
$ GarbageAttenuationOpts -> Double
_gaoCurrent (GarbageAttenuationOpts -> Double)
-> ((GarbageOpts, Gen RealWorld) -> GarbageAttenuationOpts)
-> (GarbageOpts, Gen RealWorld)
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageAttenuationOpts
f (GarbageOpts -> GarbageAttenuationOpts)
-> ((GarbageOpts, Gen RealWorld) -> GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> GarbageAttenuationOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageOpts, Gen RealWorld) -> GarbageOpts
forall a b. (a, b) -> a
fst
Gen (PrimState (ReaderT (GarbageOpts, Gen RealWorld) IO))
-> NumberProbability -> GenM' Int
forall (m :: * -> *).
PrimMonad m =>
Gen (PrimState m) -> NumberProbability -> m Int
sampleNumberProbability Gen RealWorld
Gen (PrimState (ReaderT (GarbageOpts, Gen RealWorld) IO))
gen (NumberProbability -> GenM' Int) -> NumberProbability -> GenM' Int
forall a b. (a -> b) -> a -> b
$ Double -> NumberProbability -> NumberProbability
attenuateNum Double
a NumberProbability
d
idSimpleLetter :: B.ByteString
idSimpleLetter :: ByteString
idSimpleLetter = ByteString
"ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz_0123456789$"
digitCharacter :: B.ByteString
digitCharacter :: ByteString
digitCharacter = ByteString
"0123456789"
garbageSimpleBS :: GenM' B.ByteString
garbageSimpleBS :: GenM' ByteString
garbageSimpleBS =
Word8 -> ByteString -> GenM' ByteString
avoidKW (Word8 -> ByteString -> GenM' ByteString)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (ByteString -> GenM' ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ByteString -> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
forall p.
(p -> CategoricalProbability) -> ByteString -> GenM p Word8
sampleFromString ((GarbageIdentifierOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> CategoricalProbability
_gioSimpleLetter) (Int -> ByteString -> ByteString
B.take Int
53 ByteString
idSimpleLetter)
ReaderT
(GarbageOpts, Gen RealWorld) IO (ByteString -> GenM' ByteString)
-> GenM' ByteString -> GenM' ByteString
forall (m :: * -> *) a b.
(Monad m, Applicative m) =>
m (a -> m b) -> m a -> m b
<.> (GarbageOpts -> NumberProbability)
-> (GarbageOpts -> CategoricalProbability)
-> ByteString
-> GenM' ByteString
forall p.
(p -> NumberProbability)
-> (p -> CategoricalProbability) -> ByteString -> GenM p ByteString
sampleString ((GarbageIdentifierOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> NumberProbability
_gioSimpleLetters) ((GarbageIdentifierOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> CategoricalProbability
_gioSimpleLetter) ByteString
idSimpleLetter
where
i :: (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> c
x = GarbageIdentifierOpts -> c
x (GarbageIdentifierOpts -> c)
-> (GarbageOpts -> GarbageIdentifierOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageIdentifierOpts
_goIdentifier
avoidKW :: Word8 -> ByteString -> GenM' ByteString
avoidKW Word8
fl ByteString
t =
let s :: ByteString
s = Word8 -> ByteString -> ByteString
B.cons Word8
fl ByteString
t
in if ByteString -> Bool
isKW ByteString
s
then do
Word8
x <- (GarbageOpts -> CategoricalProbability)
-> ByteString -> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
forall p.
(p -> CategoricalProbability) -> ByteString -> GenM p Word8
sampleFromString ((GarbageIdentifierOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> CategoricalProbability
_gioSimpleLetter) ByteString
idSimpleLetter
Word8 -> ByteString -> GenM' ByteString
avoidKW Word8
fl (ByteString -> GenM' ByteString) -> ByteString -> GenM' ByteString
forall a b. (a -> b) -> a -> b
$ Word8 -> ByteString -> ByteString
B.cons Word8
x ByteString
t
else ByteString -> GenM' ByteString
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
s
garbageEscapedBS :: GenM' B.ByteString
garbageEscapedBS :: GenM' ByteString
garbageEscapedBS =
[Word8] -> ByteString
B.pack ([Word8] -> ByteString)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Word8]
-> GenM' ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Word8]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageIdentifierOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> NumberProbability
_gioEscapedLetters) (Int -> Word8
forall a. Enum a => Int -> a
toEnum (Int -> Word8)
-> GenM' Int -> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability) -> Int -> Int -> GenM' Int
forall p. (p -> CategoricalProbability) -> Int -> Int -> GenM p Int
sampleSegment ((GarbageIdentifierOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> CategoricalProbability
_gioEscapedLetter) Int
33 Int
126)
where i :: (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> c
x = GarbageIdentifierOpts -> c
x (GarbageIdentifierOpts -> c)
-> (GarbageOpts -> GarbageIdentifierOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageIdentifierOpts
_goIdentifier
garbageBS :: GenM' B.ByteString
garbageBS :: GenM' ByteString
garbageBS = (GarbageOpts -> Double)
-> GenM' ByteString -> GenM' ByteString -> GenM' ByteString
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice (GarbageIdentifierOpts -> Double
_gioEscaped_Simple (GarbageIdentifierOpts -> Double)
-> (GarbageOpts -> GarbageIdentifierOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageIdentifierOpts
_goIdentifier) GenM' ByteString
garbageEscapedBS GenM' ByteString
garbageSimpleBS
garbageIdent :: GenM' Identifier
garbageIdent :: GenM' Identifier
garbageIdent = ByteString -> Identifier
Identifier (ByteString -> Identifier) -> GenM' ByteString -> GenM' Identifier
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ByteString
garbageBS
garbageIdentified :: GenM' x -> GenM' (Identified x)
garbageIdentified :: forall x. GenM' x -> GenM' (Identified x)
garbageIdentified = (Identifier -> x -> Identified x)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identified x)
forall a b c.
(a -> b -> c)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
-> ReaderT (GarbageOpts, Gen RealWorld) IO c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Identifier -> x -> Identified x
forall t. Identifier -> t -> Identified t
Identified GenM' Identifier
garbageIdent
garbageSysIdent :: GenM' B.ByteString
garbageSysIdent :: GenM' ByteString
garbageSysIdent =
Word8 -> ByteString -> ByteString
B.cons (Word8 -> ByteString -> ByteString)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (ByteString -> ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ByteString -> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
forall p.
(p -> CategoricalProbability) -> ByteString -> GenM p Word8
sampleFromString ((GarbageIdentifierOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> CategoricalProbability
_gioSystemFirstLetter) ByteString
idSimpleLetter
ReaderT (GarbageOpts, Gen RealWorld) IO (ByteString -> ByteString)
-> GenM' ByteString -> GenM' ByteString
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> (GarbageOpts -> CategoricalProbability)
-> ByteString
-> GenM' ByteString
forall p.
(p -> NumberProbability)
-> (p -> CategoricalProbability) -> ByteString -> GenM p ByteString
sampleString ((GarbageIdentifierOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> NumberProbability
_gioSystemLetters) ((GarbageIdentifierOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> CategoricalProbability
_gioSimpleLetter) ByteString
idSimpleLetter
where i :: (GarbageIdentifierOpts -> c) -> GarbageOpts -> c
i GarbageIdentifierOpts -> c
x = GarbageIdentifierOpts -> c
x (GarbageIdentifierOpts -> c)
-> (GarbageOpts -> GarbageIdentifierOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageIdentifierOpts
_goIdentifier
garbageHierIdent :: GenM' HierIdent
garbageHierIdent :: GenM' HierIdent
garbageHierIdent = do
[(Identifier, Maybe CExpr)]
hip <- (GarbageOpts -> NumberProbability)
-> GenM' (Identifier, Maybe CExpr)
-> GenM' [(Identifier, Maybe CExpr)]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive GarbageOpts -> NumberProbability
_goPathDepth (GenM' (Identifier, Maybe CExpr)
-> GenM' [(Identifier, Maybe CExpr)])
-> GenM' (Identifier, Maybe CExpr)
-> GenM' [(Identifier, Maybe CExpr)]
forall a b. (a -> b) -> a -> b
$
GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> GenM' (Identifier, Maybe CExpr)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair GenM' Identifier
garbageIdent (ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> GenM' (Identifier, Maybe CExpr))
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> GenM' (Identifier, Maybe CExpr)
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> Double)
-> GenM GarbageOpts CExpr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageExprOpts -> Double
_geoDimRange (GarbageExprOpts -> Double)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr) GenM GarbageOpts CExpr
garbageCExpr
[(Identifier, Maybe CExpr)] -> Identifier -> HierIdent
HierIdent [(Identifier, Maybe CExpr)]
hip (Identifier -> HierIdent) -> GenM' Identifier -> GenM' HierIdent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent
garbageInteger :: GenM' Natural
garbageInteger :: GenM' Natural
garbageInteger =
ByteString -> Natural
parseDecimal (ByteString -> Natural) -> GenM' ByteString -> GenM' Natural
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> (GarbageOpts -> CategoricalProbability)
-> ByteString
-> GenM' ByteString
forall p.
(p -> NumberProbability)
-> (p -> CategoricalProbability) -> ByteString -> GenM p ByteString
sampleString ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoDecimalSymbols) ((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoDecimalSymbol) ByteString
digitCharacter
where e :: (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> c
x = GarbageExprOpts -> c
x (GarbageExprOpts -> c)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr
garbageReal :: GenM' B.ByteString
garbageReal :: GenM' ByteString
garbageReal =
(GarbageOpts -> Double)
-> GenM' ByteString -> GenM' ByteString -> GenM' ByteString
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbageExprOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> Double
_geoFixed_Floating)
( do
ByteString
p <- GenM' ByteString
number
ByteString
f <- GenM' ByteString
number
ByteString -> GenM' ByteString
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> GenM' ByteString) -> ByteString -> GenM' ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
p ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"." ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
f
)
( do
ByteString
p <- GenM' ByteString
number
ByteString
f <- (GarbageOpts -> NumberProbability)
-> (GarbageOpts -> CategoricalProbability)
-> ByteString
-> GenM' ByteString
forall p.
(p -> NumberProbability)
-> (p -> CategoricalProbability) -> ByteString -> GenM p ByteString
sampleString ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoDecimalSymbols) ((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoDecimalSymbol) ByteString
digitCharacter
ByteString
s <- (GarbageOpts -> CategoricalProbability)
-> [ByteString] -> GenM' ByteString
forall p a. (p -> CategoricalProbability) -> [a] -> GenM p a
sampleFrom ((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoExponentSign) [Item [ByteString]
ByteString
"", Item [ByteString]
ByteString
"+", Item [ByteString]
ByteString
"-"]
ByteString
e <- GenM' ByteString
number
ByteString -> GenM' ByteString
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> GenM' ByteString) -> ByteString -> GenM' ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
p ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> (if ByteString -> Bool
B.null ByteString
f then ByteString
"" else Word8 -> ByteString -> ByteString
B.cons (Char -> Word8
c2w Char
'.') ByteString
f) ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"e" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
s ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
e
)
where
e :: (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> c
x = GarbageExprOpts -> c
x (GarbageExprOpts -> c)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr
number :: GenM' ByteString
number = (GarbageOpts -> NumberProbability)
-> (GarbageOpts -> CategoricalProbability)
-> ByteString
-> GenM' ByteString
forall p.
(p -> NumberProbability)
-> (p -> CategoricalProbability) -> ByteString -> GenM p ByteString
sampleNEString ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoDecimalSymbols) ((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoDecimalSymbol) ByteString
digitCharacter
garbageNumIdent :: GenM' NumIdent
garbageNumIdent :: GenM GarbageOpts NumIdent
garbageNumIdent =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts NumIdent] -> GenM GarbageOpts NumIdent
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
GarbageOpts -> CategoricalProbability
_goIntRealIdent
[ Natural -> NumIdent
NINumber (Natural -> NumIdent) -> GenM' Natural -> GenM GarbageOpts NumIdent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Natural
garbageInteger,
ByteString -> NumIdent
NIReal (ByteString -> NumIdent)
-> GenM' ByteString -> GenM GarbageOpts NumIdent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ByteString
garbageReal,
Identifier -> NumIdent
NIIdent (Identifier -> NumIdent)
-> GenM' Identifier -> GenM GarbageOpts NumIdent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent
]
garbagePrim :: GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenPrim i r a)
garbagePrim :: forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenPrim i r a)
garbagePrim GenM' i
ident Bool
attrng GenM' r
grng GenM' a
gattr =
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' (GenPrim i r a))
-> GenM' (GenPrim i r a)
forall a.
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' a)
-> GenM' a
sampleAttenuatedBranch
((GarbageExprOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> GarbageAttenuationOpts
_geoAttenuation)
((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoPrimary)
[ ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall {i} {r} {a}.
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a))
mknum (ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a)))
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall a b. (a -> b) -> a -> b
$ Bool -> Number
NXZ (Bool -> Number)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageExprOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> Double
_geoX_Z),
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall {i} {r} {a}.
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a))
mknum (ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a)))
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall a b. (a -> b) -> a -> b
$ NonEmpty BXZ -> Number
NBinary (NonEmpty BXZ -> Number)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty BXZ)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts BXZ
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty BXZ)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoBinarySymbols) ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts BXZ
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts BXZ)
-> (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts BXZ
forall a b. (a -> b) -> a -> b
$ (GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoBinarySymbol),
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall {i} {r} {a}.
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a))
mknum (ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a)))
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall a b. (a -> b) -> a -> b
$ NonEmpty OXZ -> Number
NOctal (NonEmpty OXZ -> Number)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty OXZ)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts OXZ
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty OXZ)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoOctalSymbols) ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts OXZ
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts OXZ)
-> (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts OXZ
forall a b. (a -> b) -> a -> b
$ (GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoOctalSymbol),
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall {i} {r} {a}.
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a))
mknum (ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a)))
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall a b. (a -> b) -> a -> b
$ Natural -> Number
NDecimal (Natural -> Number)
-> GenM' Natural -> ReaderT (GarbageOpts, Gen RealWorld) IO Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Natural
garbageInteger,
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall {i} {r} {a}.
ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a))
mknum (ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a)))
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, GenM' (GenPrim i r a))
forall a b. (a -> b) -> a -> b
$ NonEmpty HXZ -> Number
NHex (NonEmpty HXZ -> Number)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty HXZ)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts HXZ
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty HXZ)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoHexadecimalSymbols) ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts HXZ
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts HXZ)
-> (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts HXZ
forall a b. (a -> b) -> a -> b
$ (GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoHexadecimalSymbol),
(Bool
False, ByteString -> GenPrim i r a
forall i r a. ByteString -> GenPrim i r a
PrimReal (ByteString -> GenPrim i r a)
-> GenM' ByteString -> GenM' (GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ByteString
garbageReal),
( Bool
False,
ByteString -> GenPrim i r a
forall i r a. ByteString -> GenPrim i r a
PrimString (ByteString -> GenPrim i r a)
-> ([Word8] -> ByteString) -> [Word8] -> GenPrim i r a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
makeString (String -> ByteString)
-> ([Word8] -> String) -> [Word8] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Char) -> [Word8] -> String
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Char
w2c
([Word8] -> GenPrim i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Word8]
-> GenM' (GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Word8]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoStringCharacters) ((GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Word8)
-> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Word8
forall a b. (a -> b) -> a -> b
$ (GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoStringCharacter)
),
(Bool
attrng, i -> r -> GenPrim i r a
forall i r a. i -> r -> GenPrim i r a
PrimIdent (i -> r -> GenPrim i r a)
-> GenM' i
-> ReaderT (GarbageOpts, Gen RealWorld) IO (r -> GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' i
ident ReaderT (GarbageOpts, Gen RealWorld) IO (r -> GenPrim i r a)
-> GenM' r -> GenM' (GenPrim i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' r
grng),
( Bool
True,
do
Int
n <- Int -> Int
forall a. Enum a => a -> a
succ (Int -> Int) -> GenM' Int -> GenM' Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability) -> GenM' Int
sNum ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoConcatenations)
NonEmpty (GenExpr i r a) -> GenPrim i r a
forall i r a. NonEmpty (GenExpr i r a) -> GenPrim i r a
PrimConcat (NonEmpty (GenExpr i r a) -> GenPrim i r a)
-> ([GenExpr i r a] -> NonEmpty (GenExpr i r a))
-> [GenExpr i r a]
-> GenPrim i r a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GenExpr i r a] -> NonEmpty (GenExpr i r a)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList ([GenExpr i r a] -> GenPrim i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
-> GenM' (GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
n (Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
gexpr)
),
( Bool
True,
do
Int
n <- Int -> Int
forall a. Enum a => a -> a
succ (Int -> Int) -> GenM' Int -> GenM' Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability) -> GenM' Int
sNum ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoConcatenations)
Int -> GenM' (GenPrim i r a) -> GenM' (GenPrim i r a)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (GenM' (GenPrim i r a) -> GenM' (GenPrim i r a))
-> GenM' (GenPrim i r a) -> GenM' (GenPrim i r a)
forall a b. (a -> b) -> a -> b
$
GenExpr Identifier (Maybe CRangeExpr) a
-> NonEmpty (GenExpr i r a) -> GenPrim i r a
forall i r a.
GenExpr Identifier (Maybe CRangeExpr) a
-> NonEmpty (GenExpr i r a) -> GenPrim i r a
PrimMultConcat (GenExpr Identifier (Maybe CRangeExpr) a
-> NonEmpty (GenExpr i r a) -> GenPrim i r a)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr Identifier (Maybe CRangeExpr) a)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty (GenExpr i r a) -> GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
-> Bool
-> GenM' (Maybe CRangeExpr)
-> GenM' a
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr Identifier (Maybe CRangeExpr) a)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr
GenM' Identifier
garbageIdent
Bool
True
((GarbageOpts -> Double)
-> GenM GarbageOpts CRangeExpr -> GenM' (Maybe CRangeExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageExprOpts -> Double
_geoDimRange (GarbageExprOpts -> Double)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr) GenM GarbageOpts CRangeExpr
garbageCRangeExpr)
GenM' a
gattr
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty (GenExpr i r a) -> GenPrim i r a)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty (GenExpr i r a))
-> GenM' (GenPrim i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([GenExpr i r a] -> NonEmpty (GenExpr i r a))
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty (GenExpr i r a))
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [GenExpr i r a] -> NonEmpty (GenExpr i r a)
forall a. HasCallStack => [a] -> NonEmpty a
NE.fromList (Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
gexpr)
),
( Bool
True,
do
Int
n <- Int -> Int
forall a. Enum a => a -> a
succ (Int -> Int) -> GenM' Int -> GenM' Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability) -> GenM' Int
sNum (GarbageGenerateOpts -> NumberProbability
_ggoTaskFunPorts (GarbageGenerateOpts -> NumberProbability)
-> (GarbageOpts -> GarbageGenerateOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate)
Int -> GenM' (GenPrim i r a) -> GenM' (GenPrim i r a)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
n (GenM' (GenPrim i r a) -> GenM' (GenPrim i r a))
-> GenM' (GenPrim i r a) -> GenM' (GenPrim i r a)
forall a b. (a -> b) -> a -> b
$ i -> a -> [GenExpr i r a] -> GenPrim i r a
forall i r a. i -> a -> [GenExpr i r a] -> GenPrim i r a
PrimFun (i -> a -> [GenExpr i r a] -> GenPrim i r a)
-> GenM' i
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> [GenExpr i r a] -> GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' i
ident ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> [GenExpr i r a] -> GenPrim i r a)
-> GenM' a
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ([GenExpr i r a] -> GenPrim i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' a
gattr ReaderT
(GarbageOpts, Gen RealWorld) IO ([GenExpr i r a] -> GenPrim i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
-> GenM' (GenPrim i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
gexpr
),
(Bool
True, ByteString -> [GenExpr i r a] -> GenPrim i r a
forall i r a. ByteString -> [GenExpr i r a] -> GenPrim i r a
PrimSysFun (ByteString -> [GenExpr i r a] -> GenPrim i r a)
-> GenM' ByteString
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ([GenExpr i r a] -> GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ByteString
garbageSysIdent ReaderT
(GarbageOpts, Gen RealWorld) IO ([GenExpr i r a] -> GenPrim i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
-> GenM' (GenPrim i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [GenExpr i r a]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive ((GarbageExprOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> NumberProbability
_geoSysFunArgs) ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
gexpr),
(Bool
True, GenMinTypMax (GenExpr i r a) -> GenPrim i r a
forall i r a. GenMinTypMax (GenExpr i r a) -> GenPrim i r a
PrimMinTypMax (GenMinTypMax (GenExpr i r a) -> GenPrim i r a)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenMinTypMax (GenExpr i r a))
-> GenM' (GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenMinTypMax (GenExpr i r a))
forall e. GenM' e -> GenM' (GenMinTypMax e)
garbageGenMinTypMax ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
gexpr)
]
where
e :: (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> c
x = GarbageExprOpts -> c
x (GarbageExprOpts -> c)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr
sNum :: (GarbageOpts -> NumberProbability) -> GenM' Int
sNum = (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum ((GarbageExprOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> GarbageAttenuationOpts
_geoAttenuation)
mknum :: ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> (Bool, ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a))
mknum ReaderT (GarbageOpts, Gen RealWorld) IO Number
x =
( Bool
False,
do
Int
sz <- (GarbageOpts -> CategoricalProbability) -> Int -> Int -> GenM' Int
forall p. (p -> CategoricalProbability) -> Int -> Int -> GenM p Int
sampleSegment ((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoLiteralWidth) Int
0 Int
65535
Bool
sn <- (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageExprOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> Double
_geoLiteralSigned)
Maybe Natural -> Bool -> Number -> GenPrim i r a
forall i r a. Maybe Natural -> Bool -> Number -> GenPrim i r a
PrimNumber (if Int
sz Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Maybe Natural
forall a. Maybe a
Nothing else Natural -> Maybe Natural
forall a. a -> Maybe a
Just (Int -> Natural
forall a. Enum a => Int -> a
toEnum Int
sz)) Bool
sn (Number -> GenPrim i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Number
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO Number
x
)
gexpr :: ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
gexpr = GenM' i
-> Bool
-> GenM' r
-> GenM' a
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenExpr i r a)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr GenM' i
ident Bool
attrng GenM' r
grng GenM' a
gattr
garbageGenExpr :: GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr :: forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr GenM' i
ident Bool
attrng GenM' r
grng GenM' a
gattr =
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' (GenExpr i r a))
-> GenM' (GenExpr i r a)
forall a.
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' a)
-> GenM' a
sampleAttenuatedBranch
((GarbageExprOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> GarbageAttenuationOpts
_geoAttenuation)
((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoItem)
[ (Bool
False, GenPrim i r a -> GenExpr i r a
forall i r a. GenPrim i r a -> GenExpr i r a
ExprPrim (GenPrim i r a -> GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a)
-> GenM' (GenExpr i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' i
-> Bool
-> GenM' r
-> GenM' a
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenPrim i r a)
garbagePrim GenM' i
ident Bool
attrng GenM' r
grng GenM' a
gattr),
( Bool
False,
UnaryOperator -> a -> GenPrim i r a -> GenExpr i r a
forall i r a. UnaryOperator -> a -> GenPrim i r a -> GenExpr i r a
ExprUnOp (UnaryOperator -> a -> GenPrim i r a -> GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO UnaryOperator
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> GenPrim i r a -> GenExpr i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO UnaryOperator
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoUnary) ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> GenPrim i r a -> GenExpr i r a)
-> GenM' a
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenPrim i r a -> GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' a
gattr ReaderT
(GarbageOpts, Gen RealWorld) IO (GenPrim i r a -> GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a)
-> GenM' (GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' i
-> Bool
-> GenM' r
-> GenM' a
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenPrim i r a)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenPrim i r a)
garbagePrim GenM' i
ident Bool
attrng GenM' r
grng GenM' a
gattr
),
( Bool
True,
Int -> GenM' (GenExpr i r a) -> GenM' (GenExpr i r a)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
2 (GenM' (GenExpr i r a) -> GenM' (GenExpr i r a))
-> GenM' (GenExpr i r a) -> GenM' (GenExpr i r a)
forall a b. (a -> b) -> a -> b
$ GenExpr i r a
-> BinaryOperator -> a -> GenExpr i r a -> GenExpr i r a
forall i r a.
GenExpr i r a
-> BinaryOperator -> a -> GenExpr i r a -> GenExpr i r a
ExprBinOp (GenExpr i r a
-> BinaryOperator -> a -> GenExpr i r a -> GenExpr i r a)
-> GenM' (GenExpr i r a)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(BinaryOperator -> a -> GenExpr i r a -> GenExpr i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' (GenExpr i r a)
gexpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(BinaryOperator -> a -> GenExpr i r a -> GenExpr i r a)
-> ReaderT (GarbageOpts, Gen RealWorld) IO BinaryOperator
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> GenExpr i r a -> GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO BinaryOperator
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoBinary) ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> GenExpr i r a -> GenExpr i r a)
-> GenM' a
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenExpr i r a -> GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' a
gattr ReaderT
(GarbageOpts, Gen RealWorld) IO (GenExpr i r a -> GenExpr i r a)
-> GenM' (GenExpr i r a) -> GenM' (GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (GenExpr i r a)
gexpr
),
(Bool
True, Int -> GenM' (GenExpr i r a) -> GenM' (GenExpr i r a)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
3 (GenM' (GenExpr i r a) -> GenM' (GenExpr i r a))
-> GenM' (GenExpr i r a) -> GenM' (GenExpr i r a)
forall a b. (a -> b) -> a -> b
$ GenExpr i r a
-> a -> GenExpr i r a -> GenExpr i r a -> GenExpr i r a
forall i r a.
GenExpr i r a
-> a -> GenExpr i r a -> GenExpr i r a -> GenExpr i r a
ExprCond (GenExpr i r a
-> a -> GenExpr i r a -> GenExpr i r a -> GenExpr i r a)
-> GenM' (GenExpr i r a)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> GenExpr i r a -> GenExpr i r a -> GenExpr i r a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' (GenExpr i r a)
gexpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(a -> GenExpr i r a -> GenExpr i r a -> GenExpr i r a)
-> GenM' a
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr i r a -> GenExpr i r a -> GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' a
gattr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr i r a -> GenExpr i r a -> GenExpr i r a)
-> GenM' (GenExpr i r a)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenExpr i r a -> GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (GenExpr i r a)
gexpr ReaderT
(GarbageOpts, Gen RealWorld) IO (GenExpr i r a -> GenExpr i r a)
-> GenM' (GenExpr i r a) -> GenM' (GenExpr i r a)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (GenExpr i r a)
gexpr)
]
where
e :: (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> c
x = GarbageExprOpts -> c
x (GarbageExprOpts -> c)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr
gexpr :: GenM' (GenExpr i r a)
gexpr = GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr GenM' i
ident Bool
attrng GenM' r
grng GenM' a
gattr
garbageGenMinTypMax :: GenM' e -> GenM' (GenMinTypMax e)
garbageGenMinTypMax :: forall e. GenM' e -> GenM' (GenMinTypMax e)
garbageGenMinTypMax GenM' e
gexpr =
(GarbageOpts -> Double)
-> GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e)
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
(GarbageExprOpts -> Double
_geoMinTypMax (GarbageExprOpts -> Double)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr)
(Int
-> GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
3 (GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e))
-> GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e)
forall a b. (a -> b) -> a -> b
$ e -> e -> e -> GenMinTypMax e
forall et. et -> et -> et -> GenMinTypMax et
MTMFull (e -> e -> e -> GenMinTypMax e)
-> GenM' e
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (e -> e -> GenMinTypMax e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' e
gexpr ReaderT (GarbageOpts, Gen RealWorld) IO (e -> e -> GenMinTypMax e)
-> GenM' e
-> ReaderT (GarbageOpts, Gen RealWorld) IO (e -> GenMinTypMax e)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' e
gexpr ReaderT (GarbageOpts, Gen RealWorld) IO (e -> GenMinTypMax e)
-> GenM' e -> GenM GarbageOpts (GenMinTypMax e)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' e
gexpr)
(Int
-> GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
1 (GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e))
-> GenM GarbageOpts (GenMinTypMax e)
-> GenM GarbageOpts (GenMinTypMax e)
forall a b. (a -> b) -> a -> b
$ e -> GenMinTypMax e
forall et. et -> GenMinTypMax et
MTMSingle (e -> GenMinTypMax e)
-> GenM' e -> GenM GarbageOpts (GenMinTypMax e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' e
gexpr)
garbageRange2 :: GenM' Range2
garbageRange2 :: GenM' Range2
garbageRange2 = Int -> GenM' Range2 -> GenM' Range2
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
2 (GenM' Range2 -> GenM' Range2) -> GenM' Range2 -> GenM' Range2
forall a b. (a -> b) -> a -> b
$ CExpr -> CExpr -> Range2
Range2 (CExpr -> CExpr -> Range2)
-> GenM GarbageOpts CExpr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (CExpr -> Range2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts CExpr
garbageCExpr ReaderT (GarbageOpts, Gen RealWorld) IO (CExpr -> Range2)
-> GenM GarbageOpts CExpr -> GenM' Range2
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts CExpr
garbageCExpr
garbageDims :: GenM' [Range2]
garbageDims :: GenM' [Range2]
garbageDims = (GarbageOpts -> NumberProbability)
-> GenM' Range2 -> GenM' [Range2]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive (GarbageTypeOpts -> NumberProbability
_gtoDimensions (GarbageTypeOpts -> NumberProbability)
-> (GarbageOpts -> GarbageTypeOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageTypeOpts
_goType) GenM' Range2
garbageRange2
garbageGenRangeExpr :: GenM' e -> GenM' (GenRangeExpr e)
garbageGenRangeExpr :: forall e. GenM' e -> GenM' (GenRangeExpr e)
garbageGenRangeExpr GenM' e
ge =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts (GenRangeExpr e)]
-> GenM GarbageOpts (GenRangeExpr e)
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageExprOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> CategoricalProbability
_geoRange)
[ e -> GenRangeExpr e
forall e. e -> GenRangeExpr e
GRESingle (e -> GenRangeExpr e)
-> GenM' e -> GenM GarbageOpts (GenRangeExpr e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' e
ge,
Range2 -> GenRangeExpr e
forall e. Range2 -> GenRangeExpr e
GREPair (Range2 -> GenRangeExpr e)
-> GenM' Range2 -> GenM GarbageOpts (GenRangeExpr e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Range2
garbageRange2,
Int
-> GenM GarbageOpts (GenRangeExpr e)
-> GenM GarbageOpts (GenRangeExpr e)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion Int
2 (GenM GarbageOpts (GenRangeExpr e)
-> GenM GarbageOpts (GenRangeExpr e))
-> GenM GarbageOpts (GenRangeExpr e)
-> GenM GarbageOpts (GenRangeExpr e)
forall a b. (a -> b) -> a -> b
$
e -> Bool -> CExpr -> GenRangeExpr e
forall e. e -> Bool -> CExpr -> GenRangeExpr e
GREBaseOff (e -> Bool -> CExpr -> GenRangeExpr e)
-> GenM' e
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Bool -> CExpr -> GenRangeExpr e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' e
ge ReaderT
(GarbageOpts, Gen RealWorld) IO (Bool -> CExpr -> GenRangeExpr e)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CExpr -> GenRangeExpr e)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageExprOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> Double
_geoRangeOffsetPos_Neg) ReaderT (GarbageOpts, Gen RealWorld) IO (CExpr -> GenRangeExpr e)
-> GenM GarbageOpts CExpr -> GenM GarbageOpts (GenRangeExpr e)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts CExpr
garbageCExpr
]
where e :: (GarbageExprOpts -> c) -> GarbageOpts -> c
e GarbageExprOpts -> c
x = GarbageExprOpts -> c
x (GarbageExprOpts -> c)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr
garbageGenDimRange :: GenM' e -> GenM' (GenDimRange e)
garbageGenDimRange :: forall e. GenM' e -> GenM' (GenDimRange e)
garbageGenDimRange GenM' e
ge = do
Int
n <- (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum (GarbageExprOpts -> GarbageAttenuationOpts
_geoAttenuation (GarbageExprOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> GarbageExprOpts)
-> GarbageOpts
-> GarbageAttenuationOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr) (GarbageTypeOpts -> NumberProbability
_gtoDimensions (GarbageTypeOpts -> NumberProbability)
-> (GarbageOpts -> GarbageTypeOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageTypeOpts
_goType)
Int -> GenM' (GenDimRange e) -> GenM' (GenDimRange e)
forall a. Int -> GenM' a -> GenM' a
tameExprRecursion (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (GenM' (GenDimRange e) -> GenM' (GenDimRange e))
-> GenM' (GenDimRange e) -> GenM' (GenDimRange e)
forall a b. (a -> b) -> a -> b
$ [e] -> GenRangeExpr e -> GenDimRange e
forall e. [e] -> GenRangeExpr e -> GenDimRange e
GenDimRange ([e] -> GenRangeExpr e -> GenDimRange e)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [e]
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenRangeExpr e -> GenDimRange e)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> GenM' e -> ReaderT (GarbageOpts, Gen RealWorld) IO [e]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n GenM' e
ge ReaderT
(GarbageOpts, Gen RealWorld) IO (GenRangeExpr e -> GenDimRange e)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (GenRangeExpr e)
-> GenM' (GenDimRange e)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' e -> ReaderT (GarbageOpts, Gen RealWorld) IO (GenRangeExpr e)
forall e. GenM' e -> GenM' (GenRangeExpr e)
garbageGenRangeExpr GenM' e
ge
garbageExpr :: GenM' Expr
garbageExpr :: GenM' Expr
garbageExpr =
GenExpr HierIdent (Maybe DimRange) Attributes -> Expr
Expr (GenExpr HierIdent (Maybe DimRange) Attributes -> Expr)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr HierIdent (Maybe DimRange) Attributes)
-> GenM' Expr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
-> Bool
-> GenM' (Maybe DimRange)
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr HierIdent (Maybe DimRange) Attributes)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr
GenM' HierIdent
garbageHierIdent
Bool
True
((GarbageOpts -> Double)
-> GenM GarbageOpts DimRange -> GenM' (Maybe DimRange)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageExprOpts -> Double
_geoDimRange (GarbageExprOpts -> Double)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr) GenM GarbageOpts DimRange
garbageDimRange)
GenM' Attributes
garbageAttributes
garbageCExpr :: GenM' CExpr
garbageCExpr :: GenM GarbageOpts CExpr
garbageCExpr =
GenExpr Identifier (Maybe CRangeExpr) Attributes -> CExpr
CExpr (GenExpr Identifier (Maybe CRangeExpr) Attributes -> CExpr)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr Identifier (Maybe CRangeExpr) Attributes)
-> GenM GarbageOpts CExpr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
-> Bool
-> GenM' (Maybe CRangeExpr)
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenExpr Identifier (Maybe CRangeExpr) Attributes)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr
GenM' Identifier
garbageIdent
Bool
True
((GarbageOpts -> Double)
-> GenM GarbageOpts CRangeExpr -> GenM' (Maybe CRangeExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageExprOpts -> Double
_geoDimRange (GarbageExprOpts -> Double)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr) GenM GarbageOpts CRangeExpr
garbageCRangeExpr)
GenM' Attributes
garbageAttributes
garbageRangeExpr :: GenM' RangeExpr
garbageRangeExpr :: GenM' RangeExpr
garbageRangeExpr = GenM' Expr -> GenM' RangeExpr
forall e. GenM' e -> GenM' (GenRangeExpr e)
garbageGenRangeExpr GenM' Expr
garbageExpr
garbageCRangeExpr :: GenM' CRangeExpr
garbageCRangeExpr :: GenM GarbageOpts CRangeExpr
garbageCRangeExpr = GenM GarbageOpts CExpr -> GenM GarbageOpts CRangeExpr
forall e. GenM' e -> GenM' (GenRangeExpr e)
garbageGenRangeExpr GenM GarbageOpts CExpr
garbageCExpr
garbageDimRange :: GenM' DimRange
garbageDimRange :: GenM GarbageOpts DimRange
garbageDimRange = GenM' Expr -> GenM GarbageOpts DimRange
forall e. GenM' e -> GenM' (GenDimRange e)
garbageGenDimRange GenM' Expr
garbageExpr
garbageCDimRange :: GenM' CDimRange
garbageCDimRange :: GenM' CDimRange
garbageCDimRange = GenM GarbageOpts CExpr -> GenM' CDimRange
forall e. GenM' e -> GenM' (GenDimRange e)
garbageGenDimRange GenM GarbageOpts CExpr
garbageCExpr
garbageMinTypMax :: GenM' MinTypMax
garbageMinTypMax :: GenM' MinTypMax
garbageMinTypMax = GenM' Expr -> GenM' MinTypMax
forall e. GenM' e -> GenM' (GenMinTypMax e)
garbageGenMinTypMax GenM' Expr
garbageExpr
garbageCMinTypMax :: GenM' CMinTypMax
garbageCMinTypMax :: GenM' CMinTypMax
garbageCMinTypMax = GenM GarbageOpts CExpr -> GenM' CMinTypMax
forall e. GenM' e -> GenM' (GenMinTypMax e)
garbageGenMinTypMax GenM GarbageOpts CExpr
garbageCExpr
garbageBareCMTM :: GenM' CMinTypMax
garbageBareCMTM :: GenM' CMinTypMax
garbageBareCMTM =
(GarbageOpts -> Double)
-> GenM' CMinTypMax -> GenM' CMinTypMax -> GenM' CMinTypMax
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
(GarbageOpts -> Double
_goBareMinTypMax)
(CExpr -> CExpr -> CExpr -> CMinTypMax
forall et. et -> et -> et -> GenMinTypMax et
MTMFull (CExpr -> CExpr -> CExpr -> CMinTypMax)
-> GenM GarbageOpts CExpr
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CExpr -> CExpr -> CMinTypMax)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts CExpr
garbageCExpr ReaderT
(GarbageOpts, Gen RealWorld) IO (CExpr -> CExpr -> CMinTypMax)
-> GenM GarbageOpts CExpr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (CExpr -> CMinTypMax)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts CExpr
garbageCExpr ReaderT (GarbageOpts, Gen RealWorld) IO (CExpr -> CMinTypMax)
-> GenM GarbageOpts CExpr -> GenM' CMinTypMax
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts CExpr
garbageCExpr)
(CExpr -> CMinTypMax
forall et. et -> GenMinTypMax et
MTMSingle (CExpr -> CMinTypMax) -> GenM GarbageOpts CExpr -> GenM' CMinTypMax
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts CExpr
garbageCExpr)
garbageAttributes :: GenM' Attributes
garbageAttributes :: GenM' Attributes
garbageAttributes =
(GarbageOpts -> NumberProbability)
-> GenM' [Attribute] -> GenM' Attributes
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive GarbageOpts -> NumberProbability
_goAttributes (GenM' [Attribute] -> GenM' Attributes)
-> GenM' [Attribute] -> GenM' Attributes
forall a b. (a -> b) -> a -> b
$
(GarbageOpts -> NumberProbability)
-> GenM' Attribute -> GenM' [Attribute]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive GarbageOpts -> NumberProbability
_goAttributes (GenM' Attribute -> GenM' [Attribute])
-> GenM' Attribute -> GenM' [Attribute]
forall a b. (a -> b) -> a -> b
$
ByteString
-> Maybe (GenExpr Identifier (Maybe CRangeExpr) ()) -> Attribute
Attribute (ByteString
-> Maybe (GenExpr Identifier (Maybe CRangeExpr) ()) -> Attribute)
-> GenM' ByteString
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (GenExpr Identifier (Maybe CRangeExpr) ()) -> Attribute)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ByteString
garbageBS ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (GenExpr Identifier (Maybe CRangeExpr) ()) -> Attribute)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (GenExpr Identifier (Maybe CRangeExpr) ()))
-> GenM' Attribute
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM GarbageOpts (GenExpr Identifier (Maybe CRangeExpr) ())
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (GenExpr Identifier (Maybe CRangeExpr) ()))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe GarbageOpts -> Double
_goAttributeOptionalValue GenM GarbageOpts (GenExpr Identifier (Maybe CRangeExpr) ())
gattr
where
gattr :: GenM GarbageOpts (GenExpr Identifier (Maybe CRangeExpr) ())
gattr =
GenM' Identifier
-> Bool
-> GenM' (Maybe CRangeExpr)
-> GenM' ()
-> GenM GarbageOpts (GenExpr Identifier (Maybe CRangeExpr) ())
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr
GenM' Identifier
garbageIdent
Bool
True
((GarbageOpts -> Double)
-> GenM GarbageOpts CRangeExpr -> GenM' (Maybe CRangeExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageExprOpts -> Double
_geoDimRange (GarbageExprOpts -> Double)
-> (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageExprOpts
_goExpr) GenM GarbageOpts CRangeExpr
garbageCRangeExpr)
(() -> GenM' ()
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
garbageAttributed :: GenM' x -> GenM' (Attributed x)
garbageAttributed :: forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed = (Attributes -> x -> Attributed x)
-> GenM' Attributes
-> ReaderT (GarbageOpts, Gen RealWorld) IO x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Attributed x)
forall a b c.
(a -> b -> c)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
-> ReaderT (GarbageOpts, Gen RealWorld) IO c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 Attributes -> x -> Attributed x
forall t. Attributes -> t -> Attributed t
Attributed GenM' Attributes
garbageAttributes
garbageAttrIded :: GenM' x -> GenM' (AttrIded x)
garbageAttrIded :: forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded = (Attributes -> Identifier -> x -> AttrIded x)
-> GenM' Attributes
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (AttrIded x)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
liftA3 Attributes -> Identifier -> x -> AttrIded x
forall t. Attributes -> Identifier -> t -> AttrIded t
AttrIded GenM' Attributes
garbageAttributes GenM' Identifier
garbageIdent
garbageDelay1 :: GenM' Delay1
garbageDelay1 :: GenM GarbageOpts Delay1
garbageDelay1 =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts Delay1] -> GenM GarbageOpts Delay1
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
GarbageOpts -> CategoricalProbability
_goDelay
[ NumIdent -> Delay1
D1Base (NumIdent -> Delay1)
-> GenM GarbageOpts NumIdent -> GenM GarbageOpts Delay1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts NumIdent
garbageNumIdent,
MinTypMax -> Delay1
D11 (MinTypMax -> Delay1) -> GenM' MinTypMax -> GenM GarbageOpts Delay1
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' MinTypMax
garbageMinTypMax
]
garbageDelay2 :: GenM' Delay2
garbageDelay2 :: GenM GarbageOpts Delay2
garbageDelay2 =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts Delay2] -> GenM GarbageOpts Delay2
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
GarbageOpts -> CategoricalProbability
_goDelay
[ NumIdent -> Delay2
D2Base (NumIdent -> Delay2)
-> GenM GarbageOpts NumIdent -> GenM GarbageOpts Delay2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts NumIdent
garbageNumIdent,
MinTypMax -> Delay2
D21 (MinTypMax -> Delay2) -> GenM' MinTypMax -> GenM GarbageOpts Delay2
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' MinTypMax
garbageMinTypMax,
MinTypMax -> MinTypMax -> Delay2
D22 (MinTypMax -> MinTypMax -> Delay2)
-> GenM' MinTypMax
-> ReaderT (GarbageOpts, Gen RealWorld) IO (MinTypMax -> Delay2)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' MinTypMax
garbageMinTypMax ReaderT (GarbageOpts, Gen RealWorld) IO (MinTypMax -> Delay2)
-> GenM' MinTypMax -> GenM GarbageOpts Delay2
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MinTypMax
garbageMinTypMax
]
garbageDelay3 :: GenM' Delay3
garbageDelay3 :: GenM GarbageOpts Delay3
garbageDelay3 =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts Delay3] -> GenM GarbageOpts Delay3
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
GarbageOpts -> CategoricalProbability
_goDelay
[ NumIdent -> Delay3
D3Base (NumIdent -> Delay3)
-> GenM GarbageOpts NumIdent -> GenM GarbageOpts Delay3
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts NumIdent
garbageNumIdent,
MinTypMax -> Delay3
D31 (MinTypMax -> Delay3) -> GenM' MinTypMax -> GenM GarbageOpts Delay3
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' MinTypMax
garbageMinTypMax,
MinTypMax -> MinTypMax -> Delay3
D32 (MinTypMax -> MinTypMax -> Delay3)
-> GenM' MinTypMax
-> ReaderT (GarbageOpts, Gen RealWorld) IO (MinTypMax -> Delay3)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' MinTypMax
garbageMinTypMax ReaderT (GarbageOpts, Gen RealWorld) IO (MinTypMax -> Delay3)
-> GenM' MinTypMax -> GenM GarbageOpts Delay3
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MinTypMax
garbageMinTypMax,
MinTypMax -> MinTypMax -> MinTypMax -> Delay3
D33 (MinTypMax -> MinTypMax -> MinTypMax -> Delay3)
-> GenM' MinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (MinTypMax -> MinTypMax -> Delay3)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' MinTypMax
garbageMinTypMax ReaderT
(GarbageOpts, Gen RealWorld) IO (MinTypMax -> MinTypMax -> Delay3)
-> GenM' MinTypMax
-> ReaderT (GarbageOpts, Gen RealWorld) IO (MinTypMax -> Delay3)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MinTypMax
garbageMinTypMax ReaderT (GarbageOpts, Gen RealWorld) IO (MinTypMax -> Delay3)
-> GenM' MinTypMax -> GenM GarbageOpts Delay3
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MinTypMax
garbageMinTypMax
]
garbageLValue :: GenM' dr -> GenM' (LValue dr)
garbageLValue :: forall dr. GenM' dr -> GenM' (LValue dr)
garbageLValue GenM' dr
gdr = do
[LValue dr]
l <- (GarbageOpts -> NumberProbability)
-> GenM' (LValue dr) -> GenM' [LValue dr]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatExprRecursive GarbageOpts -> NumberProbability
_goLValues (GenM' (LValue dr) -> GenM' [LValue dr])
-> GenM' (LValue dr) -> GenM' [LValue dr]
forall a b. (a -> b) -> a -> b
$ GenM' dr -> GenM' (LValue dr)
forall dr. GenM' dr -> GenM' (LValue dr)
garbageLValue GenM' dr
gdr
case [LValue dr]
l of
[] -> HierIdent -> Maybe dr -> LValue dr
forall dr. HierIdent -> Maybe dr -> LValue dr
LVSingle (HierIdent -> Maybe dr -> LValue dr)
-> GenM' HierIdent
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe dr -> LValue dr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
garbageHierIdent ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe dr -> LValue dr)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe dr)
-> GenM' (LValue dr)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM' dr -> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe dr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe GarbageOpts -> Double
_goOptionalLValue GenM' dr
gdr
LValue dr
h : [LValue dr]
t -> LValue dr -> GenM' (LValue dr)
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (LValue dr -> GenM' (LValue dr)) -> LValue dr -> GenM' (LValue dr)
forall a b. (a -> b) -> a -> b
$ NonEmpty (LValue dr) -> LValue dr
forall dr. NonEmpty (LValue dr) -> LValue dr
LVConcat (NonEmpty (LValue dr) -> LValue dr)
-> NonEmpty (LValue dr) -> LValue dr
forall a b. (a -> b) -> a -> b
$ LValue dr
h LValue dr -> [LValue dr] -> NonEmpty (LValue dr)
forall a. a -> [a] -> NonEmpty a
:| [LValue dr]
t
garbageNetLV :: GenM' NetLValue
garbageNetLV :: GenM' NetLValue
garbageNetLV = GenM' CDimRange -> GenM' NetLValue
forall dr. GenM' dr -> GenM' (LValue dr)
garbageLValue GenM' CDimRange
garbageCDimRange
garbageVarLV :: GenM' VarLValue
garbageVarLV :: GenM' VarLValue
garbageVarLV = GenM GarbageOpts DimRange -> GenM' VarLValue
forall dr. GenM' dr -> GenM' (LValue dr)
garbageLValue GenM GarbageOpts DimRange
garbageDimRange
garbageVarAssign :: GenM' VarAssign
garbageVarAssign :: GenM' VarAssign
garbageVarAssign = VarLValue -> Expr -> VarAssign
forall dr. LValue dr -> Expr -> Assign dr
Assign (VarLValue -> Expr -> VarAssign)
-> GenM' VarLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> VarAssign)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' VarLValue
garbageVarLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> VarAssign)
-> GenM' Expr -> GenM' VarAssign
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr
garbageNetAssign :: GenM' NetAssign
garbageNetAssign :: GenM' NetAssign
garbageNetAssign = NetLValue -> Expr -> NetAssign
forall dr. LValue dr -> Expr -> Assign dr
Assign (NetLValue -> Expr -> NetAssign)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> NetAssign)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> NetAssign)
-> GenM' Expr -> GenM' NetAssign
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr
garbageEvCtl :: GenM' EventControl
garbageEvCtl :: GenM GarbageOpts EventControl
garbageEvCtl =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts EventControl] -> GenM GarbageOpts EventControl
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoEvent)
[ EventControl -> GenM GarbageOpts EventControl
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EventControl
ECDeps,
HierIdent -> EventControl
ECIdent (HierIdent -> EventControl)
-> GenM' HierIdent -> GenM GarbageOpts EventControl
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
garbageHierIdent,
NonEmpty EventPrim -> EventControl
ECExpr (NonEmpty EventPrim -> EventControl)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty EventPrim)
-> GenM GarbageOpts EventControl
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts EventPrim
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty EventPrim)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE
((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoEvents)
(EventPrefix -> Expr -> EventPrim
EventPrim (EventPrefix -> Expr -> EventPrim)
-> ReaderT (GarbageOpts, Gen RealWorld) IO EventPrefix
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> EventPrim)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO EventPrefix
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoEventPrefix) ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> EventPrim)
-> GenM' Expr -> GenM GarbageOpts EventPrim
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr)
]
where s :: (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> c
x = GarbageStatementOpts -> c
x (GarbageStatementOpts -> c)
-> (GarbageOpts -> GarbageStatementOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement
garbageDelEvCtl :: GenM' DelayEventControl
garbageDelEvCtl :: GenM GarbageOpts DelayEventControl
garbageDelEvCtl =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts DelayEventControl]
-> GenM GarbageOpts DelayEventControl
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
(GarbageStatementOpts -> CategoricalProbability
_gstoDelayEventRepeat (GarbageStatementOpts -> CategoricalProbability)
-> (GarbageOpts -> GarbageStatementOpts)
-> GarbageOpts
-> CategoricalProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement)
[ Delay1 -> DelayEventControl
DECDelay (Delay1 -> DelayEventControl)
-> GenM GarbageOpts Delay1 -> GenM GarbageOpts DelayEventControl
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts Delay1
garbageDelay1,
EventControl -> DelayEventControl
DECEvent (EventControl -> DelayEventControl)
-> GenM GarbageOpts EventControl
-> GenM GarbageOpts DelayEventControl
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts EventControl
garbageEvCtl,
Expr -> EventControl -> DelayEventControl
DECRepeat (Expr -> EventControl -> DelayEventControl)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (EventControl -> DelayEventControl)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld) IO (EventControl -> DelayEventControl)
-> GenM GarbageOpts EventControl
-> GenM GarbageOpts DelayEventControl
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts EventControl
garbageEvCtl
]
garbageLoopStatement :: GenM' LoopStatement
garbageLoopStatement :: GenM GarbageOpts LoopStatement
garbageLoopStatement =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts LoopStatement]
-> GenM GarbageOpts LoopStatement
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
(GarbageStatementOpts -> CategoricalProbability
_gstoLoop (GarbageStatementOpts -> CategoricalProbability)
-> (GarbageOpts -> GarbageStatementOpts)
-> GarbageOpts
-> CategoricalProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement)
[ LoopStatement -> GenM GarbageOpts LoopStatement
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure LoopStatement
LSForever,
Expr -> LoopStatement
LSRepeat (Expr -> LoopStatement)
-> GenM' Expr -> GenM GarbageOpts LoopStatement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Expr
garbageExpr,
Expr -> LoopStatement
LSWhile (Expr -> LoopStatement)
-> GenM' Expr -> GenM GarbageOpts LoopStatement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Expr
garbageExpr,
VarAssign -> Expr -> VarAssign -> LoopStatement
LSFor (VarAssign -> Expr -> VarAssign -> LoopStatement)
-> GenM' VarAssign
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> VarAssign -> LoopStatement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' VarAssign
garbageVarAssign ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> VarAssign -> LoopStatement)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (VarAssign -> LoopStatement)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld) IO (VarAssign -> LoopStatement)
-> GenM' VarAssign -> GenM GarbageOpts LoopStatement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' VarAssign
garbageVarAssign
]
garbageStmtBlockHeader :: GenM' (Maybe (Identifier, [AttrIded StdBlockDecl]))
=
(GarbageOpts -> Double)
-> GenM GarbageOpts (Identifier, [AttrIded StdBlockDecl])
-> GenM' (Maybe (Identifier, [AttrIded StdBlockDecl]))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoBlockHeader) (GenM GarbageOpts (Identifier, [AttrIded StdBlockDecl])
-> GenM' (Maybe (Identifier, [AttrIded StdBlockDecl])))
-> GenM GarbageOpts (Identifier, [AttrIded StdBlockDecl])
-> GenM' (Maybe (Identifier, [AttrIded StdBlockDecl]))
forall a b. (a -> b) -> a -> b
$
GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded StdBlockDecl]
-> GenM GarbageOpts (Identifier, [AttrIded StdBlockDecl])
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair GenM' Identifier
garbageIdent (ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded StdBlockDecl]
-> GenM GarbageOpts (Identifier, [AttrIded StdBlockDecl]))
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded StdBlockDecl]
-> GenM GarbageOpts (Identifier, [AttrIded StdBlockDecl])
forall a b. (a -> b) -> a -> b
$
(GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (AttrIded StdBlockDecl)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded StdBlockDecl]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoBlockDecls) (GenM GarbageOpts (AttrIded StdBlockDecl)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded StdBlockDecl])
-> GenM GarbageOpts (AttrIded StdBlockDecl)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded StdBlockDecl]
forall a b. (a -> b) -> a -> b
$
GenM' StdBlockDecl -> GenM GarbageOpts (AttrIded StdBlockDecl)
forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded (GenM' StdBlockDecl -> GenM GarbageOpts (AttrIded StdBlockDecl))
-> GenM' StdBlockDecl -> GenM GarbageOpts (AttrIded StdBlockDecl)
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> CategoricalProbability)
-> [GenM' StdBlockDecl] -> GenM' StdBlockDecl
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch ((GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoBlockDecl) [GenM' StdBlockDecl]
stdBlockDeclList
where
s :: (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> c
x = GarbageStatementOpts -> c
x (GarbageStatementOpts -> c)
-> (GarbageOpts -> GarbageStatementOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement
garbageFunctionStatement :: GenM' FunctionStatement
garbageFunctionStatement :: GenM' FunctionStatement
garbageFunctionStatement =
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' FunctionStatement)
-> GenM' FunctionStatement
forall a.
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' a)
-> GenM' a
sampleAttenuatedBranch
((GarbageStatementOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> GarbageAttenuationOpts
_gstoAttenuation)
((GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoItem)
[ (Bool
False, VarAssign -> FunctionStatement
FSBlockAssign (VarAssign -> FunctionStatement)
-> GenM' VarAssign -> GenM' FunctionStatement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' VarAssign
garbageVarAssign),
( Bool
True,
do
ZOX
x <- (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX)
-> (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX
forall a b. (a -> b) -> a -> b
$ (GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoCase
Expr
e <- GenM' Expr
garbageExpr
Int
pn <- (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum ((GarbageStatementOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> GarbageAttenuationOpts
_gstoAttenuation) ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoCaseBranches)
Attributed (Maybe FunctionStatement)
d <- Int
-> GenM' (Attributed (Maybe FunctionStatement))
-> GenM' (Attributed (Maybe FunctionStatement))
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
pn GenM' (Attributed (Maybe FunctionStatement))
gmybfstmt
let n :: Int
n = if Attributed (Maybe FunctionStatement)
d Attributed (Maybe FunctionStatement)
-> Attributed (Maybe FunctionStatement) -> Bool
forall a. Eq a => a -> a -> Bool
== Attributes
-> Maybe FunctionStatement -> Attributed (Maybe FunctionStatement)
forall t. Attributes -> t -> Attributed t
Attributed [] Maybe FunctionStatement
forall a. Maybe a
Nothing then Int
pn Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
pn
[FCaseItem]
c <-
Int -> GenM' [FCaseItem] -> GenM' [FCaseItem]
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
n (GenM' [FCaseItem] -> GenM' [FCaseItem])
-> GenM' [FCaseItem] -> GenM' [FCaseItem]
forall a b. (a -> b) -> a -> b
$
Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO FCaseItem
-> GenM' [FCaseItem]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n (ReaderT (GarbageOpts, Gen RealWorld) IO FCaseItem
-> GenM' [FCaseItem])
-> ReaderT (GarbageOpts, Gen RealWorld) IO FCaseItem
-> GenM' [FCaseItem]
forall a b. (a -> b) -> a -> b
$
NonEmpty Expr -> Attributed (Maybe FunctionStatement) -> FCaseItem
FCaseItem (NonEmpty Expr
-> Attributed (Maybe FunctionStatement) -> FCaseItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Attributed (Maybe FunctionStatement) -> FCaseItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoCaseBranchPatterns) GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Attributed (Maybe FunctionStatement) -> FCaseItem)
-> GenM' (Attributed (Maybe FunctionStatement))
-> ReaderT (GarbageOpts, Gen RealWorld) IO FCaseItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (Attributed (Maybe FunctionStatement))
gmybfstmt
FunctionStatement -> GenM' FunctionStatement
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (FunctionStatement -> GenM' FunctionStatement)
-> FunctionStatement -> GenM' FunctionStatement
forall a b. (a -> b) -> a -> b
$ ZOX
-> Expr
-> [FCaseItem]
-> Attributed (Maybe FunctionStatement)
-> FunctionStatement
FSCase ZOX
x Expr
e [FCaseItem]
c Attributed (Maybe FunctionStatement)
d
),
(Bool
True, Int -> GenM' FunctionStatement -> GenM' FunctionStatement
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
2 (GenM' FunctionStatement -> GenM' FunctionStatement)
-> GenM' FunctionStatement -> GenM' FunctionStatement
forall a b. (a -> b) -> a -> b
$ Expr
-> Attributed (Maybe FunctionStatement)
-> Attributed (Maybe FunctionStatement)
-> FunctionStatement
FSIf (Expr
-> Attributed (Maybe FunctionStatement)
-> Attributed (Maybe FunctionStatement)
-> FunctionStatement)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Attributed (Maybe FunctionStatement)
-> Attributed (Maybe FunctionStatement) -> FunctionStatement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Attributed (Maybe FunctionStatement)
-> Attributed (Maybe FunctionStatement) -> FunctionStatement)
-> GenM' (Attributed (Maybe FunctionStatement))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Attributed (Maybe FunctionStatement) -> FunctionStatement)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (Attributed (Maybe FunctionStatement))
gmybfstmt ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Attributed (Maybe FunctionStatement) -> FunctionStatement)
-> GenM' (Attributed (Maybe FunctionStatement))
-> GenM' FunctionStatement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (Attributed (Maybe FunctionStatement))
gmybfstmt),
(Bool
False, HierIdent -> FunctionStatement
FSDisable (HierIdent -> FunctionStatement)
-> GenM' HierIdent -> GenM' FunctionStatement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
garbageHierIdent),
(Bool
True, LoopStatement -> AttrFStmt -> FunctionStatement
FSLoop (LoopStatement -> AttrFStmt -> FunctionStatement)
-> GenM GarbageOpts LoopStatement
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (AttrFStmt -> FunctionStatement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts LoopStatement
garbageLoopStatement ReaderT
(GarbageOpts, Gen RealWorld) IO (AttrFStmt -> FunctionStatement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
-> GenM' FunctionStatement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
1 ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
gattrfstmt),
( Bool
True,
Maybe (Identifier, [AttrIded StdBlockDecl])
-> Bool -> [AttrFStmt] -> FunctionStatement
FSBlock (Maybe (Identifier, [AttrIded StdBlockDecl])
-> Bool -> [AttrFStmt] -> FunctionStatement)
-> GenM' (Maybe (Identifier, [AttrIded StdBlockDecl]))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Bool -> [AttrFStmt] -> FunctionStatement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' (Maybe (Identifier, [AttrIded StdBlockDecl]))
garbageStmtBlockHeader
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Bool -> [AttrFStmt] -> FunctionStatement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ([AttrFStmt] -> FunctionStatement)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoBlockPar_Seq)
ReaderT
(GarbageOpts, Gen RealWorld) IO ([AttrFStmt] -> FunctionStatement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrFStmt]
-> GenM' FunctionStatement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrFStmt]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatStmtRecursive ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoItems) ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
gattrfstmt
)
]
where
s :: (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> c
x = GarbageStatementOpts -> c
x (GarbageStatementOpts -> c)
-> (GarbageOpts -> GarbageStatementOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement
gmybfstmt :: GenM' (Attributed (Maybe FunctionStatement))
gmybfstmt = GenM' (Maybe FunctionStatement)
-> GenM' (Attributed (Maybe FunctionStatement))
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed (GenM' (Maybe FunctionStatement)
-> GenM' (Attributed (Maybe FunctionStatement)))
-> GenM' (Maybe FunctionStatement)
-> GenM' (Attributed (Maybe FunctionStatement))
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> Double)
-> GenM' FunctionStatement -> GenM' (Maybe FunctionStatement)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoOptional) GenM' FunctionStatement
garbageFunctionStatement
gattrfstmt :: ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
gattrfstmt = GenM' FunctionStatement
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrFStmt
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed GenM' FunctionStatement
garbageFunctionStatement
garbageStatement :: GenM' Statement
garbageStatement :: GenM' Statement
garbageStatement =
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' Statement)
-> GenM' Statement
forall a.
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' a)
-> GenM' a
sampleAttenuatedBranch
((GarbageStatementOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> GarbageAttenuationOpts
_gstoAttenuation)
((GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoItem)
[ ( Bool
False,
Bool -> VarAssign -> Maybe DelayEventControl -> Statement
SBlockAssign (Bool -> VarAssign -> Maybe DelayEventControl -> Statement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(VarAssign -> Maybe DelayEventControl -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoAssignmentBlocking)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(VarAssign -> Maybe DelayEventControl -> Statement)
-> GenM' VarAssign
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe DelayEventControl -> Statement)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' VarAssign
garbageVarAssign
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe DelayEventControl -> Statement)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe DelayEventControl)
-> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM GarbageOpts DelayEventControl
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe DelayEventControl)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoOptionalDelEvCtl) GenM GarbageOpts DelayEventControl
garbageDelEvCtl
),
( Bool
True,
do
ZOX
x <- (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX)
-> (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX
forall a b. (a -> b) -> a -> b
$ (GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoCase
Expr
e <- GenM' Expr
garbageExpr
Int
pn <- (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum ((GarbageStatementOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> GarbageAttenuationOpts
_gstoAttenuation) ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoCaseBranches)
MybStmt
d <- Int -> GenM' MybStmt -> GenM' MybStmt
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
pn GenM' MybStmt
garbageMybStmt
let n :: Int
n = if MybStmt
d MybStmt -> MybStmt -> Bool
forall a. Eq a => a -> a -> Bool
== Attributes -> Maybe Statement -> MybStmt
forall t. Attributes -> t -> Attributed t
Attributed [] Maybe Statement
forall a. Maybe a
Nothing then Int
pn Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
pn
[CaseItem]
c <-
Int -> GenM' [CaseItem] -> GenM' [CaseItem]
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
n (GenM' [CaseItem] -> GenM' [CaseItem])
-> GenM' [CaseItem] -> GenM' [CaseItem]
forall a b. (a -> b) -> a -> b
$
Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO CaseItem
-> GenM' [CaseItem]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n (ReaderT (GarbageOpts, Gen RealWorld) IO CaseItem
-> GenM' [CaseItem])
-> ReaderT (GarbageOpts, Gen RealWorld) IO CaseItem
-> GenM' [CaseItem]
forall a b. (a -> b) -> a -> b
$
NonEmpty Expr -> MybStmt -> CaseItem
CaseItem (NonEmpty Expr -> MybStmt -> CaseItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> CaseItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoCaseBranchPatterns) GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> CaseItem)
-> GenM' MybStmt
-> ReaderT (GarbageOpts, Gen RealWorld) IO CaseItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MybStmt
garbageMybStmt
Statement -> GenM' Statement
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Statement -> GenM' Statement) -> Statement -> GenM' Statement
forall a b. (a -> b) -> a -> b
$ ZOX -> Expr -> [CaseItem] -> MybStmt -> Statement
SCase ZOX
x Expr
e [CaseItem]
c MybStmt
d
),
(Bool
True, Int -> GenM' Statement -> GenM' Statement
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
2 (GenM' Statement -> GenM' Statement)
-> GenM' Statement -> GenM' Statement
forall a b. (a -> b) -> a -> b
$ Expr -> MybStmt -> MybStmt -> Statement
SIf (Expr -> MybStmt -> MybStmt -> Statement)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (MybStmt -> MybStmt -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld) IO (MybStmt -> MybStmt -> Statement)
-> GenM' MybStmt
-> ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> Statement)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MybStmt
garbageMybStmt ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> Statement)
-> GenM' MybStmt -> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MybStmt
garbageMybStmt),
(Bool
False, HierIdent -> Statement
SDisable (HierIdent -> Statement) -> GenM' HierIdent -> GenM' Statement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
garbageHierIdent),
(Bool
True, LoopStatement -> AttrStmt -> Statement
SLoop (LoopStatement -> AttrStmt -> Statement)
-> GenM GarbageOpts LoopStatement
-> ReaderT (GarbageOpts, Gen RealWorld) IO (AttrStmt -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts LoopStatement
garbageLoopStatement ReaderT (GarbageOpts, Gen RealWorld) IO (AttrStmt -> Statement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
-> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
1 ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
garbageAttrStmt),
( Bool
True,
Maybe (Identifier, [AttrIded StdBlockDecl])
-> Bool -> [AttrStmt] -> Statement
SBlock (Maybe (Identifier, [AttrIded StdBlockDecl])
-> Bool -> [AttrStmt] -> Statement)
-> GenM' (Maybe (Identifier, [AttrIded StdBlockDecl]))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Bool -> [AttrStmt] -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' (Maybe (Identifier, [AttrIded StdBlockDecl]))
garbageStmtBlockHeader
ReaderT
(GarbageOpts, Gen RealWorld) IO (Bool -> [AttrStmt] -> Statement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ([AttrStmt] -> Statement)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoBlockPar_Seq)
ReaderT (GarbageOpts, Gen RealWorld) IO ([AttrStmt] -> Statement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrStmt]
-> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrStmt]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatStmtRecursive ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoItems) ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
garbageAttrStmt
),
( Bool
False,
HierIdent -> [Expr] -> Statement
SEventTrigger (HierIdent -> [Expr] -> Statement)
-> GenM' HierIdent
-> ReaderT (GarbageOpts, Gen RealWorld) IO ([Expr] -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
garbageHierIdent ReaderT (GarbageOpts, Gen RealWorld) IO ([Expr] -> Statement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Expr]
-> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' Expr -> ReaderT (GarbageOpts, Gen RealWorld) IO [Expr]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN (GarbageTypeOpts -> NumberProbability
_gtoDimensions (GarbageTypeOpts -> NumberProbability)
-> (GarbageOpts -> GarbageTypeOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageTypeOpts
_goType) GenM' Expr
garbageExpr
),
( Bool
False,
ProcContAssign -> Statement
SProcContAssign (ProcContAssign -> Statement)
-> GenM GarbageOpts ProcContAssign -> GenM' Statement
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts ProcContAssign]
-> GenM GarbageOpts ProcContAssign
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoProcContAssign)
[ VarAssign -> ProcContAssign
PCAAssign (VarAssign -> ProcContAssign)
-> GenM' VarAssign -> GenM GarbageOpts ProcContAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' VarAssign
garbageVarAssign,
VarLValue -> ProcContAssign
PCADeassign (VarLValue -> ProcContAssign)
-> GenM' VarLValue -> GenM GarbageOpts ProcContAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' VarLValue
garbageVarLV,
Either VarAssign NetAssign -> ProcContAssign
PCAForce (Either VarAssign NetAssign -> ProcContAssign)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Either VarAssign NetAssign)
-> GenM GarbageOpts ProcContAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> GenM' VarAssign
-> GenM' NetAssign
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Either VarAssign NetAssign)
forall p a b.
(p -> Double) -> GenM p a -> GenM p b -> GenM p (Either a b)
sampleEither ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoPCAVar_Net) GenM' VarAssign
garbageVarAssign GenM' NetAssign
garbageNetAssign,
Either VarLValue NetLValue -> ProcContAssign
PCARelease (Either VarLValue NetLValue -> ProcContAssign)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Either VarLValue NetLValue)
-> GenM GarbageOpts ProcContAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> GenM' VarLValue
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Either VarLValue NetLValue)
forall p a b.
(p -> Double) -> GenM p a -> GenM p b -> GenM p (Either a b)
sampleEither ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoPCAVar_Net) GenM' VarLValue
garbageVarLV GenM' NetLValue
garbageNetLV
]
),
( Bool
True,
Either Delay1 EventControl -> MybStmt -> Statement
SProcTimingControl (Either Delay1 EventControl -> MybStmt -> Statement)
-> GenM GarbageOpts (Either Delay1 EventControl)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts (Either Delay1 EventControl)]
-> GenM GarbageOpts (Either Delay1 EventControl)
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageStatementOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> CategoricalProbability
_gstoDelayEventRepeat)
[Delay1 -> Either Delay1 EventControl
forall a b. a -> Either a b
Left (Delay1 -> Either Delay1 EventControl)
-> GenM GarbageOpts Delay1
-> GenM GarbageOpts (Either Delay1 EventControl)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts Delay1
garbageDelay1, EventControl -> Either Delay1 EventControl
forall a b. b -> Either a b
Right (EventControl -> Either Delay1 EventControl)
-> GenM GarbageOpts EventControl
-> GenM GarbageOpts (Either Delay1 EventControl)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts EventControl
garbageEvCtl]
ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> Statement)
-> GenM' MybStmt -> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> GenM' MybStmt -> GenM' MybStmt
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
1 GenM' MybStmt
garbageMybStmt
),
( Bool
False,
ByteString -> [Maybe Expr] -> Statement
SSysTaskEnable (ByteString -> [Maybe Expr] -> Statement)
-> GenM' ByteString
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ([Maybe Expr] -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ByteString
garbageSysIdent
ReaderT (GarbageOpts, Gen RealWorld) IO ([Maybe Expr] -> Statement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Maybe Expr]
-> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (Maybe Expr)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Maybe Expr]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageStatementOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> NumberProbability
_gstoSysTaskPorts) ((GarbageOpts -> Double)
-> GenM' Expr -> GenM GarbageOpts (Maybe Expr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageStatementOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> Double
_gstoSysTaskOptionalPort) GenM' Expr
garbageExpr)
),
( Bool
False,
HierIdent -> [Expr] -> Statement
STaskEnable (HierIdent -> [Expr] -> Statement)
-> GenM' HierIdent
-> ReaderT (GarbageOpts, Gen RealWorld) IO ([Expr] -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
garbageHierIdent ReaderT (GarbageOpts, Gen RealWorld) IO ([Expr] -> Statement)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Expr]
-> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' Expr -> ReaderT (GarbageOpts, Gen RealWorld) IO [Expr]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN (GarbageGenerateOpts -> NumberProbability
_ggoTaskFunPorts (GarbageGenerateOpts -> NumberProbability)
-> (GarbageOpts -> GarbageGenerateOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate) GenM' Expr
garbageExpr
),
(Bool
True, Expr -> MybStmt -> Statement
SWait (Expr -> MybStmt -> Statement)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> Statement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> Statement)
-> GenM' MybStmt -> GenM' Statement
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> GenM' MybStmt -> GenM' MybStmt
forall a. Int -> GenM' a -> GenM' a
tameStmtRecursion Int
1 GenM' MybStmt
garbageMybStmt)
]
where s :: (GarbageStatementOpts -> c) -> GarbageOpts -> c
s GarbageStatementOpts -> c
x = GarbageStatementOpts -> c
x (GarbageStatementOpts -> c)
-> (GarbageOpts -> GarbageStatementOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement
garbageMybStmt :: GenM' MybStmt
garbageMybStmt :: GenM' MybStmt
garbageMybStmt = GenM' (Maybe Statement) -> GenM' MybStmt
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed (GenM' (Maybe Statement) -> GenM' MybStmt)
-> GenM' (Maybe Statement) -> GenM' MybStmt
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> Double)
-> GenM' Statement -> GenM' (Maybe Statement)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageStatementOpts -> Double
_gstoOptional (GarbageStatementOpts -> Double)
-> (GarbageOpts -> GarbageStatementOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageStatementOpts
_goStatement) GenM' Statement
garbageStatement
garbageAttrStmt :: GenM' AttrStmt
garbageAttrStmt :: ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
garbageAttrStmt = GenM' Statement -> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed GenM' Statement
garbageStatement
garbageSR :: GenM' SignRange
garbageSR :: GenM' SignRange
garbageSR =
Bool -> Maybe Range2 -> SignRange
SignRange (Bool -> Maybe Range2 -> SignRange)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe Range2 -> SignRange)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageTypeOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageTypeOpts -> c) -> GarbageOpts -> c
t GarbageTypeOpts -> Double
_gtoConcreteSignedness)
ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2 -> SignRange)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> GenM' SignRange
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM' Range2
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageTypeOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageTypeOpts -> c) -> GarbageOpts -> c
t GarbageTypeOpts -> Double
_gtoConcreteBitRange) GenM' Range2
garbageRange2
where t :: (GarbageTypeOpts -> c) -> GarbageOpts -> c
t GarbageTypeOpts -> c
x = GarbageTypeOpts -> c
x (GarbageTypeOpts -> c)
-> (GarbageOpts -> GarbageTypeOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageTypeOpts
_goType
garbageComType :: GenM' x -> GenM' (ComType x)
garbageComType :: forall x. GenM' x -> GenM' (ComType x)
garbageComType GenM' x
m =
(GarbageOpts -> Double)
-> GenM GarbageOpts (ComType x)
-> GenM GarbageOpts (ComType x)
-> GenM GarbageOpts (ComType x)
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbageTypeOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageTypeOpts -> c) -> GarbageOpts -> c
t GarbageTypeOpts -> Double
_gtoAbstract_Concrete)
(AbsType -> ComType x
forall t. AbsType -> ComType t
CTAbstract (AbsType -> ComType x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AbsType
-> GenM GarbageOpts (ComType x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AbsType
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageTypeOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageTypeOpts -> c) -> GarbageOpts -> c
t GarbageTypeOpts -> CategoricalProbability
_gtoAbstract))
(x -> SignRange -> ComType x
forall t. t -> SignRange -> ComType t
CTConcrete (x -> SignRange -> ComType x)
-> GenM' x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (SignRange -> ComType x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' x
m ReaderT (GarbageOpts, Gen RealWorld) IO (SignRange -> ComType x)
-> GenM' SignRange -> GenM GarbageOpts (ComType x)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' SignRange
garbageSR)
where t :: (GarbageTypeOpts -> c) -> GarbageOpts -> c
t GarbageTypeOpts -> c
x = GarbageTypeOpts -> c
x (GarbageTypeOpts -> c)
-> (GarbageOpts -> GarbageTypeOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageTypeOpts
_goType
garbageParameter :: GenM' Parameter
garbageParameter :: GenM' Parameter
garbageParameter = ComType () -> CMinTypMax -> Parameter
Parameter (ComType () -> CMinTypMax -> Parameter)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> Parameter)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
forall x. GenM' x -> GenM' (ComType x)
garbageComType (GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ()))
-> GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
forall a b. (a -> b) -> a -> b
$ () -> GenM' ()
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) ReaderT (GarbageOpts, Gen RealWorld) IO (CMinTypMax -> Parameter)
-> GenM' CMinTypMax -> GenM' Parameter
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageBareCMTM
blockDeclList :: (forall x. GenM' x -> GenM' (f x)) -> GenM' t -> [GenM' (BlockDecl f t)]
blockDeclList :: forall (f :: * -> *) t.
(forall x. GenM' x -> GenM' (f x))
-> GenM' t -> [GenM' (BlockDecl f t)]
blockDeclList forall x. GenM' x -> GenM' (f x)
f GenM' t
m =
[ SignRange -> f t -> BlockDecl f t
forall (f :: * -> *) t. SignRange -> f t -> BlockDecl f t
BDReg (SignRange -> f t -> BlockDecl f t)
-> GenM' SignRange
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f t -> BlockDecl f t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' SignRange
garbageSR ReaderT (GarbageOpts, Gen RealWorld) IO (f t -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
-> GenM' (BlockDecl f t)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' t -> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
forall x. GenM' x -> GenM' (f x)
f GenM' t
m,
f t -> BlockDecl f t
forall (f :: * -> *) t. f t -> BlockDecl f t
BDInt (f t -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
-> GenM' (BlockDecl f t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' t -> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
forall x. GenM' x -> GenM' (f x)
f GenM' t
m,
f t -> BlockDecl f t
forall (f :: * -> *) t. f t -> BlockDecl f t
BDReal (f t -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
-> GenM' (BlockDecl f t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' t -> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
forall x. GenM' x -> GenM' (f x)
f GenM' t
m,
f t -> BlockDecl f t
forall (f :: * -> *) t. f t -> BlockDecl f t
BDTime (f t -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
-> GenM' (BlockDecl f t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' t -> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
forall x. GenM' x -> GenM' (f x)
f GenM' t
m,
f t -> BlockDecl f t
forall (f :: * -> *) t. f t -> BlockDecl f t
BDRealTime (f t -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
-> GenM' (BlockDecl f t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' t -> ReaderT (GarbageOpts, Gen RealWorld) IO (f t)
forall x. GenM' x -> GenM' (f x)
f GenM' t
m,
f [Range2] -> BlockDecl f t
forall (f :: * -> *) t. f [Range2] -> BlockDecl f t
BDEvent (f [Range2] -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f [Range2])
-> GenM' (BlockDecl f t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' [Range2]
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f [Range2])
forall x. GenM' x -> GenM' (f x)
f GenM' [Range2]
garbageDims,
ComType () -> f CMinTypMax -> BlockDecl f t
forall (f :: * -> *) t. ComType () -> f CMinTypMax -> BlockDecl f t
BDLocalParam (ComType () -> f CMinTypMax -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f CMinTypMax -> BlockDecl f t)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
forall x. GenM' x -> GenM' (ComType x)
garbageComType (GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ()))
-> GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
forall a b. (a -> b) -> a -> b
$ () -> GenM' ()
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) ReaderT
(GarbageOpts, Gen RealWorld) IO (f CMinTypMax -> BlockDecl f t)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f CMinTypMax)
-> GenM' (BlockDecl f t)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f CMinTypMax)
forall x. GenM' x -> GenM' (f x)
f GenM' CMinTypMax
garbageBareCMTM
]
stdBlockDeclList :: [GenM' StdBlockDecl]
stdBlockDeclList :: [GenM' StdBlockDecl]
stdBlockDeclList =
(ReaderT
(GarbageOpts, Gen RealWorld) IO (BlockDecl Identity [Range2])
-> GenM' StdBlockDecl)
-> [ReaderT
(GarbageOpts, Gen RealWorld) IO (BlockDecl Identity [Range2])]
-> [GenM' StdBlockDecl]
forall a b. (a -> b) -> [a] -> [b]
map ((BlockDecl Identity [Range2] -> StdBlockDecl)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (BlockDecl Identity [Range2])
-> GenM' StdBlockDecl
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BlockDecl Identity [Range2] -> StdBlockDecl
SBDBlockDecl) ((forall x. GenM' x -> GenM' (Identity x))
-> GenM' [Range2]
-> [ReaderT
(GarbageOpts, Gen RealWorld) IO (BlockDecl Identity [Range2])]
forall (f :: * -> *) t.
(forall x. GenM' x -> GenM' (f x))
-> GenM' t -> [GenM' (BlockDecl f t)]
blockDeclList ((x -> Identity x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity x)
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap x -> Identity x
forall a. a -> Identity a
Identity) GenM' [Range2]
garbageDims)
[GenM' StdBlockDecl]
-> [GenM' StdBlockDecl] -> [GenM' StdBlockDecl]
forall a. [a] -> [a] -> [a]
++ [Parameter -> StdBlockDecl
SBDParameter (Parameter -> StdBlockDecl)
-> GenM' Parameter -> GenM' StdBlockDecl
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Parameter
garbageParameter]
garbageDriveStrength :: GenM' DriveStrength
garbageDriveStrength :: GenM' DriveStrength
garbageDriveStrength = do
Maybe Strength
x <- GenM GarbageOpts (Maybe Strength)
strall
Maybe Strength
y <- GenM GarbageOpts (Maybe Strength)
strall
case (Maybe Strength
x, Maybe Strength
y) of
(Just Strength
a, Just Strength
b) -> DriveStrength -> GenM' DriveStrength
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (DriveStrength -> GenM' DriveStrength)
-> DriveStrength -> GenM' DriveStrength
forall a b. (a -> b) -> a -> b
$ Strength -> Strength -> DriveStrength
DSNormal Strength
a Strength
b
(Maybe Strength
Nothing, Just Strength
b) -> DriveStrength -> GenM' DriveStrength
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (DriveStrength -> GenM' DriveStrength)
-> DriveStrength -> GenM' DriveStrength
forall a b. (a -> b) -> a -> b
$ Bool -> Strength -> DriveStrength
DSHighZ Bool
False Strength
b
(Just Strength
a, Maybe Strength
Nothing) -> DriveStrength -> GenM' DriveStrength
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (DriveStrength -> GenM' DriveStrength)
-> DriveStrength -> GenM' DriveStrength
forall a b. (a -> b) -> a -> b
$ Bool -> Strength -> DriveStrength
DSHighZ Bool
True Strength
a
(Maybe Strength, Maybe Strength)
_ -> GenM' DriveStrength
garbageDriveStrength
where strall :: GenM GarbageOpts (Maybe Strength)
strall = (GarbageOpts -> CategoricalProbability)
-> GenM GarbageOpts (Maybe Strength)
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p (Maybe a)
sampleMaybeEnum GarbageOpts -> CategoricalProbability
_goDriveStrength
garbageTFBlockDecl :: GenM' x -> GenM' (TFBlockDecl x)
garbageTFBlockDecl :: forall x. GenM' x -> GenM' (TFBlockDecl x)
garbageTFBlockDecl GenM' x
m =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts (TFBlockDecl x)]
-> GenM GarbageOpts (TFBlockDecl x)
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch ((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoTaskFunDecl) ([GenM GarbageOpts (TFBlockDecl x)]
-> GenM GarbageOpts (TFBlockDecl x))
-> [GenM GarbageOpts (TFBlockDecl x)]
-> GenM GarbageOpts (TFBlockDecl x)
forall a b. (a -> b) -> a -> b
$ (GenM' StdBlockDecl -> GenM GarbageOpts (TFBlockDecl x))
-> [GenM' StdBlockDecl] -> [GenM GarbageOpts (TFBlockDecl x)]
forall a b. (a -> b) -> [a] -> [b]
map ((StdBlockDecl -> TFBlockDecl x)
-> GenM' StdBlockDecl -> GenM GarbageOpts (TFBlockDecl x)
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap StdBlockDecl -> TFBlockDecl x
forall t. StdBlockDecl -> TFBlockDecl t
TFBDStd) [GenM' StdBlockDecl]
stdBlockDeclList [GenM GarbageOpts (TFBlockDecl x)]
-> [GenM GarbageOpts (TFBlockDecl x)]
-> [GenM GarbageOpts (TFBlockDecl x)]
forall a. [a] -> [a] -> [a]
++
[x -> ComType Bool -> TFBlockDecl x
forall t. t -> ComType Bool -> TFBlockDecl t
TFBDPort (x -> ComType Bool -> TFBlockDecl x)
-> GenM' x
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (ComType Bool -> TFBlockDecl x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' x
m ReaderT
(GarbageOpts, Gen RealWorld) IO (ComType Bool -> TFBlockDecl x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType Bool)
-> GenM GarbageOpts (TFBlockDecl x)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType Bool)
forall x. GenM' x -> GenM' (ComType x)
garbageComType ((GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool)
-> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall a b. (a -> b) -> a -> b
$ (GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoTaskFunRegister)]
where g :: (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> c
x = GarbageGenerateOpts -> c
x (GarbageGenerateOpts -> c)
-> (GarbageOpts -> GarbageGenerateOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate
garbageInstanceName :: GenM' InstanceName
garbageInstanceName :: GenM' InstanceName
garbageInstanceName =
Identifier -> Maybe Range2 -> InstanceName
InstanceName (Identifier -> Maybe Range2 -> InstanceName)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe Range2 -> InstanceName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe Range2 -> InstanceName)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> GenM' InstanceName
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM' Range2
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageGenerateOpts -> Double
_ggoInstOptionalRange (GarbageGenerateOpts -> Double)
-> (GarbageOpts -> GarbageGenerateOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate) GenM' Range2
garbageRange2
garbageGateInst :: (forall x. GenM' x -> GenM' (f x)) -> GenM' (ModGenItem f)
forall x. GenM' x -> GenM' (f x)
f =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts (ModGenItem f)]
-> GenM GarbageOpts (ModGenItem f)
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoGateInst)
[ ReaderT (GarbageOpts, Gen RealWorld) IO (f GICMos -> ModGenItem f)
-> GenM' GICMos -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Maybe Delay3 -> f GICMos -> ModGenItem f
forall (f :: * -> *).
Bool -> Maybe Delay3 -> f GICMos -> ModGenItem f
MGICMos Bool
False (Maybe Delay3 -> f GICMos -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GICMos -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GICMos -> GenM GarbageOpts (ModGenItem f))
-> GenM' GICMos -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> Expr -> GICMos
GICMos (Maybe InstanceName -> NetLValue -> Expr -> Expr -> Expr -> GICMos)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> Expr -> GICMos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> Expr -> GICMos)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> Expr -> GICMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> Expr -> GICMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GICMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GICMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GICMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GICMos)
-> GenM' Expr -> GenM' GICMos
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GICMos -> ModGenItem f)
-> GenM' GICMos -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Maybe Delay3 -> f GICMos -> ModGenItem f
forall (f :: * -> *).
Bool -> Maybe Delay3 -> f GICMos -> ModGenItem f
MGICMos Bool
True (Maybe Delay3 -> f GICMos -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GICMos -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GICMos -> GenM GarbageOpts (ModGenItem f))
-> GenM' GICMos -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> Expr -> GICMos
GICMos (Maybe InstanceName -> NetLValue -> Expr -> Expr -> Expr -> GICMos)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> Expr -> GICMos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> Expr -> GICMos)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> Expr -> GICMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> Expr -> GICMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GICMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GICMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GICMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GICMos)
-> GenM' Expr -> GenM' GICMos
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
forall (f :: * -> *).
Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
MGIEnable Bool
False Bool
False (DriveStrength -> Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIEnable -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable
GIEnable (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
-> GenM' Expr -> GenM' GIEnable
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
forall (f :: * -> *).
Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
MGIEnable Bool
False Bool
True (DriveStrength -> Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIEnable -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable
GIEnable (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
-> GenM' Expr -> GenM' GIEnable
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
forall (f :: * -> *).
Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
MGIEnable Bool
True Bool
False (DriveStrength -> Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIEnable -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable
GIEnable (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
-> GenM' Expr -> GenM' GIEnable
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
forall (f :: * -> *).
Bool
-> Bool
-> DriveStrength
-> Maybe Delay3
-> f GIEnable
-> ModGenItem f
MGIEnable Bool
True Bool
True (DriveStrength -> Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f GIEnable -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIEnable -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIEnable -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIEnable -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable
GIEnable (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIEnable)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIEnable)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIEnable)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIEnable)
-> GenM' Expr -> GenM' GIEnable
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
MGIMos Bool
False Bool
False (Maybe Delay3 -> f GIMos -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIMos -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos
GIMos (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
-> GenM' Expr -> GenM' GIMos
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
MGIMos Bool
False Bool
True (Maybe Delay3 -> f GIMos -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIMos -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos
GIMos (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
-> GenM' Expr -> GenM' GIMos
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
MGIMos Bool
True Bool
False (Maybe Delay3 -> f GIMos -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIMos -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos
GIMos (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
-> GenM' Expr -> GenM' GIMos
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay3 -> f GIMos -> ModGenItem f
MGIMos Bool
True Bool
True (Maybe Delay3 -> f GIMos -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIMos -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3) (GenM' GIMos -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIMos -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos
GIMos (Maybe InstanceName -> NetLValue -> Expr -> Expr -> GIMos)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> Expr -> Expr -> GIMos)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> Expr -> GIMos)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIMos)
-> GenM' Expr -> GenM' GIMos
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GINIn -> ModGenItem f)
-> GenM' GINIn -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf
((NInputType
-> Bool
-> DriveStrength
-> Maybe Delay2
-> f GINIn
-> ModGenItem f)
-> Bool
-> NInputType
-> DriveStrength
-> Maybe Delay2
-> f GINIn
-> ModGenItem f
forall a b c. (a -> b -> c) -> b -> a -> c
flip NInputType
-> Bool -> DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f
forall (f :: * -> *).
NInputType
-> Bool -> DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f
MGINIn Bool
False (NInputType
-> DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NInputType
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NInputType
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoGateNInputType) ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINIn -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINIn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GINIn -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2)
(Maybe InstanceName -> NetLValue -> NonEmpty Expr -> GINIn
GINIn (Maybe InstanceName -> NetLValue -> NonEmpty Expr -> GINIn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NonEmpty Expr -> GINIn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NonEmpty Expr -> GINIn)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr -> GINIn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr -> GINIn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
-> GenM' GINIn
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoGateInputs) GenM' Expr
garbageExpr),
ReaderT (GarbageOpts, Gen RealWorld) IO (f GINIn -> ModGenItem f)
-> GenM' GINIn -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf
((NInputType
-> Bool
-> DriveStrength
-> Maybe Delay2
-> f GINIn
-> ModGenItem f)
-> Bool
-> NInputType
-> DriveStrength
-> Maybe Delay2
-> f GINIn
-> ModGenItem f
forall a b c. (a -> b -> c) -> b -> a -> c
flip NInputType
-> Bool -> DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f
forall (f :: * -> *).
NInputType
-> Bool -> DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f
MGINIn Bool
True (NInputType
-> DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NInputType
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NInputType
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoGateNInputType) ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> Maybe Delay2 -> f GINIn -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINIn -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINIn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GINIn -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2)
(Maybe InstanceName -> NetLValue -> NonEmpty Expr -> GINIn
GINIn (Maybe InstanceName -> NetLValue -> NonEmpty Expr -> GINIn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NonEmpty Expr -> GINIn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NonEmpty Expr -> GINIn)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr -> GINIn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr -> GINIn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
-> GenM' GINIn
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoGateInputs) GenM' Expr
garbageExpr),
ReaderT (GarbageOpts, Gen RealWorld) IO (f GINOut -> ModGenItem f)
-> GenM' GINOut -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> DriveStrength -> Maybe Delay2 -> f GINOut -> ModGenItem f
forall (f :: * -> *).
Bool -> DriveStrength -> Maybe Delay2 -> f GINOut -> ModGenItem f
MGINOut Bool
False (DriveStrength -> Maybe Delay2 -> f GINOut -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINOut -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINOut -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GINOut -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2) (GenM' GINOut -> GenM GarbageOpts (ModGenItem f))
-> GenM' GINOut -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NonEmpty NetLValue -> Expr -> GINOut
GINOut (Maybe InstanceName -> NonEmpty NetLValue -> Expr -> GINOut)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty NetLValue -> Expr -> GINOut)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty NetLValue -> Expr -> GINOut)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty NetLValue)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GINOut)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty NetLValue)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoGateOutputs) GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GINOut)
-> GenM' Expr -> GenM' GINOut
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GINOut -> ModGenItem f)
-> GenM' GINOut -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> DriveStrength -> Maybe Delay2 -> f GINOut -> ModGenItem f
forall (f :: * -> *).
Bool -> DriveStrength -> Maybe Delay2 -> f GINOut -> ModGenItem f
MGINOut Bool
True (DriveStrength -> Maybe Delay2 -> f GINOut -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINOut -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f GINOut -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GINOut -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2) (GenM' GINOut -> GenM GarbageOpts (ModGenItem f))
-> GenM' GINOut -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NonEmpty NetLValue -> Expr -> GINOut
GINOut (Maybe InstanceName -> NonEmpty NetLValue -> Expr -> GINOut)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty NetLValue -> Expr -> GINOut)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty NetLValue -> Expr -> GINOut)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty NetLValue)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GINOut)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty NetLValue)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoGateOutputs) GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GINOut)
-> GenM' Expr -> GenM' GINOut
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
MGIPassEn Bool
False Bool
False (Maybe Delay2 -> f GIPassEn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2) (GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn
GIPassEn (Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
-> GenM' Expr -> GenM' GIPassEn
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
MGIPassEn Bool
False Bool
True (Maybe Delay2 -> f GIPassEn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2) (GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn
GIPassEn (Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
-> GenM' Expr -> GenM' GIPassEn
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
MGIPassEn Bool
True Bool
False (Maybe Delay2 -> f GIPassEn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2) (GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn
GIPassEn (Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
-> GenM' Expr -> GenM' GIPassEn
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
forall (f :: * -> *).
Bool -> Bool -> Maybe Delay2 -> f GIPassEn -> ModGenItem f
MGIPassEn Bool
True Bool
True (Maybe Delay2 -> f GIPassEn -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPassEn -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2) (GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPassEn -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$
Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn
GIPassEn (Maybe InstanceName -> NetLValue -> NetLValue -> Expr -> GIPassEn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> Expr -> GIPassEn)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> GIPassEn)
-> GenM' Expr -> GenM' GIPassEn
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f)
-> GenM' GIPass -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf ((f GIPass -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f)
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((f GIPass -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f))
-> (f GIPass -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f)
forall a b. (a -> b) -> a -> b
$ Bool -> f GIPass -> ModGenItem f
forall (f :: * -> *). Bool -> f GIPass -> ModGenItem f
MGIPass Bool
False) (GenM' GIPass -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPass -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$ Maybe InstanceName -> NetLValue -> NetLValue -> GIPass
GIPass (Maybe InstanceName -> NetLValue -> NetLValue -> GIPass)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> NetLValue -> GIPass)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> NetLValue -> GIPass)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPass)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPass)
-> GenM' NetLValue -> GenM' GIPass
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f)
-> GenM' GIPass -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf ((f GIPass -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f)
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((f GIPass -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f))
-> (f GIPass -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPass -> ModGenItem f)
forall a b. (a -> b) -> a -> b
$ Bool -> f GIPass -> ModGenItem f
forall (f :: * -> *). Bool -> f GIPass -> ModGenItem f
MGIPass Bool
True) (GenM' GIPass -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPass -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$ Maybe InstanceName -> NetLValue -> NetLValue -> GIPass
GIPass (Maybe InstanceName -> NetLValue -> NetLValue -> GIPass)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> NetLValue -> GIPass)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT
(GarbageOpts, Gen RealWorld) IO (NetLValue -> NetLValue -> GIPass)
-> GenM' NetLValue
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPass)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPass)
-> GenM' NetLValue -> GenM' GIPass
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIPull -> ModGenItem f)
-> GenM' GIPull -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> DriveStrength -> f GIPull -> ModGenItem f
forall (f :: * -> *).
Bool -> DriveStrength -> f GIPull -> ModGenItem f
MGIPull Bool
False (DriveStrength -> f GIPull -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPull -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength) (GenM' GIPull -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPull -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$ Maybe InstanceName -> NetLValue -> GIPull
GIPull (Maybe InstanceName -> NetLValue -> GIPull)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPull)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPull)
-> GenM' NetLValue -> GenM' GIPull
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV,
ReaderT (GarbageOpts, Gen RealWorld) IO (f GIPull -> ModGenItem f)
-> GenM' GIPull -> GenM GarbageOpts (ModGenItem f)
forall {x} {b}.
ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf (Bool -> DriveStrength -> f GIPull -> ModGenItem f
forall (f :: * -> *).
Bool -> DriveStrength -> f GIPull -> ModGenItem f
MGIPull Bool
True (DriveStrength -> f GIPull -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f GIPull -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength) (GenM' GIPull -> GenM GarbageOpts (ModGenItem f))
-> GenM' GIPull -> GenM GarbageOpts (ModGenItem f)
forall a b. (a -> b) -> a -> b
$ Maybe InstanceName -> NetLValue -> GIPull
GIPull (Maybe InstanceName -> NetLValue -> GIPull)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPull)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname ReaderT (GarbageOpts, Gen RealWorld) IO (NetLValue -> GIPull)
-> GenM' NetLValue -> GenM' GIPull
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV
]
where
g :: (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> c
x = GarbageGenerateOpts -> c
x (GarbageGenerateOpts -> c)
-> (GarbageOpts -> GarbageGenerateOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate
mkf :: ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO b
mkf ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
c GenM' x
m = ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
c ReaderT (GarbageOpts, Gen RealWorld) IO (f x -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' x -> ReaderT (GarbageOpts, Gen RealWorld) IO (f x)
forall x. GenM' x -> GenM' (f x)
f GenM' x
m
optname :: ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
optname = (GarbageOpts -> Double)
-> GenM' InstanceName
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoGateOptIdent) GenM' InstanceName
garbageInstanceName
optd3 :: ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3 = (GarbageOpts -> Double)
-> GenM GarbageOpts Delay3
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoInstOptionalDelay) GenM GarbageOpts Delay3
garbageDelay3
optd2 :: ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2 = (GarbageOpts -> Double)
-> GenM GarbageOpts Delay2
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoInstOptionalDelay) GenM GarbageOpts Delay2
garbageDelay2
garbageGenIf :: GenM' ModGenCondItem
garbageGenIf :: GenM' ModGenCondItem
garbageGenIf =
Int -> GenM' ModGenCondItem -> GenM' ModGenCondItem
forall a. Int -> GenM' a -> GenM' a
tameModGenRecursion Int
2 (GenM' ModGenCondItem -> GenM' ModGenCondItem)
-> GenM' ModGenCondItem -> GenM' ModGenCondItem
forall a b. (a -> b) -> a -> b
$ CExpr -> GenerateCondBlock -> GenerateCondBlock -> ModGenCondItem
MGCIIf (CExpr -> GenerateCondBlock -> GenerateCondBlock -> ModGenCondItem)
-> GenM GarbageOpts CExpr
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenerateCondBlock -> GenerateCondBlock -> ModGenCondItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts CExpr
garbageCExpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenerateCondBlock -> GenerateCondBlock -> ModGenCondItem)
-> GenM' GenerateCondBlock
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenerateCondBlock -> ModGenCondItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' GenerateCondBlock
garbageGenCondBlock ReaderT
(GarbageOpts, Gen RealWorld)
IO
(GenerateCondBlock -> ModGenCondItem)
-> GenM' GenerateCondBlock -> GenM' ModGenCondItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' GenerateCondBlock
garbageGenCondBlock
garbageGenCase :: GenM' ModGenCondItem
garbageGenCase :: GenM' ModGenCondItem
garbageGenCase = do
CExpr
e <- GenM GarbageOpts CExpr
garbageCExpr
Int
pn <- (GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> NumberProbability) -> GenM' Int
sampleAttenuatedNum ((GarbageGenerateOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> GarbageAttenuationOpts
_ggoAttenuation) ((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoCaseBranches)
GenerateCondBlock
d <- Int -> GenM' GenerateCondBlock -> GenM' GenerateCondBlock
forall a. Int -> GenM' a -> GenM' a
tameModGenRecursion Int
pn GenM' GenerateCondBlock
garbageGenCondBlock
let n :: Int
n = if GenerateCondBlock
d GenerateCondBlock -> GenerateCondBlock -> Bool
forall a. Eq a => a -> a -> Bool
== GenerateCondBlock
GCBEmpty then Int
pn Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
pn
[GenCaseItem]
c <-
Int -> GenM' [GenCaseItem] -> GenM' [GenCaseItem]
forall a. Int -> GenM' a -> GenM' a
tameModGenRecursion Int
n (GenM' [GenCaseItem] -> GenM' [GenCaseItem])
-> GenM' [GenCaseItem] -> GenM' [GenCaseItem]
forall a b. (a -> b) -> a -> b
$
Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenCaseItem
-> GenM' [GenCaseItem]
forall (m :: * -> *) a. Applicative m => Int -> m a -> m [a]
replicateM Int
n (ReaderT (GarbageOpts, Gen RealWorld) IO GenCaseItem
-> GenM' [GenCaseItem])
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenCaseItem
-> GenM' [GenCaseItem]
forall a b. (a -> b) -> a -> b
$
NonEmpty CExpr -> GenerateCondBlock -> GenCaseItem
GenCaseItem (NonEmpty CExpr -> GenerateCondBlock -> GenCaseItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty CExpr)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenerateCondBlock -> GenCaseItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts CExpr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty CExpr)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoCaseBranchPatterns) GenM GarbageOpts CExpr
garbageCExpr ReaderT
(GarbageOpts, Gen RealWorld) IO (GenerateCondBlock -> GenCaseItem)
-> GenM' GenerateCondBlock
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenCaseItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' GenerateCondBlock
garbageGenCondBlock
ModGenCondItem -> GenM' ModGenCondItem
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (ModGenCondItem -> GenM' ModGenCondItem)
-> ModGenCondItem -> GenM' ModGenCondItem
forall a b. (a -> b) -> a -> b
$ CExpr -> [GenCaseItem] -> GenerateCondBlock -> ModGenCondItem
MGCICase CExpr
e [GenCaseItem]
c GenerateCondBlock
d
where g :: (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> c
x = GarbageGenerateOpts -> c
x (GarbageGenerateOpts -> c)
-> (GarbageOpts -> GarbageGenerateOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate
garbageModGenItem :: (forall x. GenM' x -> GenM' (f x)) -> GenM' (ModGenItem f)
garbageModGenItem :: forall (f :: * -> *).
(forall x. GenM' x -> GenM' (f x)) -> GenM' (ModGenItem f)
garbageModGenItem forall x. GenM' x -> GenM' (f x)
f =
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' (ModGenItem f))
-> GenM' (ModGenItem f)
forall a.
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' a)
-> GenM' a
sampleAttenuatedBranch
((GarbageGenerateOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> GarbageAttenuationOpts
_ggoAttenuation)
((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoItem)
[ ( Bool
False,
NetType -> DriveStrength -> NetProp -> f NetInit -> ModGenItem f
forall (f :: * -> *).
NetType -> DriveStrength -> NetProp -> f NetInit -> ModGenItem f
MGINetInit (NetType -> DriveStrength -> NetProp -> f NetInit -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetType
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> NetProp -> f NetInit -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetType
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoNetType) ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> NetProp -> f NetInit -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetInit -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetInit -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f NetInit -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
gnetprop ReaderT (GarbageOpts, Gen RealWorld) IO (f NetInit -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetInit)
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetInit
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetInit)
forall x. GenM' x -> GenM' (f x)
f GenM' NetInit
gnetinit
),
(Bool
False, NetType -> NetProp -> f NetDecl -> ModGenItem f
forall (f :: * -> *).
NetType -> NetProp -> f NetDecl -> ModGenItem f
MGINetDecl (NetType -> NetProp -> f NetDecl -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetType
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetDecl -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetType
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoNetType) ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetDecl -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f NetDecl -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
gnetprop ReaderT (GarbageOpts, Gen RealWorld) IO (f NetDecl -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetDecl)
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetDecl
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetDecl)
forall x. GenM' x -> GenM' (f x)
f GenM' NetDecl
gnetdecl),
(Bool
False, DriveStrength -> NetProp -> f NetInit -> ModGenItem f
forall (f :: * -> *).
DriveStrength -> NetProp -> f NetInit -> ModGenItem f
MGITriD (DriveStrength -> NetProp -> f NetInit -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetInit -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetInit -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f NetInit -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
gnetprop ReaderT (GarbageOpts, Gen RealWorld) IO (f NetInit -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetInit)
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetInit
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetInit)
forall x. GenM' x -> GenM' (f x)
f GenM' NetInit
gnetinit),
(Bool
False, ChargeStrength -> NetProp -> f NetDecl -> ModGenItem f
forall (f :: * -> *).
ChargeStrength -> NetProp -> f NetDecl -> ModGenItem f
MGITriC (ChargeStrength -> NetProp -> f NetDecl -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO ChargeStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetDecl -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO ChargeStrength
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoChargeStrength) ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetProp -> f NetDecl -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f NetDecl -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
gnetprop ReaderT (GarbageOpts, Gen RealWorld) IO (f NetDecl -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetDecl)
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetDecl
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetDecl)
forall x. GenM' x -> GenM' (f x)
f GenM' NetDecl
gnetdecl),
( Bool
False,
BlockDecl (Compose f Identified) (Either [Range2] CExpr)
-> ModGenItem f
forall (f :: * -> *).
BlockDecl (Compose f Identified) (Either [Range2] CExpr)
-> ModGenItem f
MGIBlockDecl (BlockDecl (Compose f Identified) (Either [Range2] CExpr)
-> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(BlockDecl (Compose f Identified) (Either [Range2] CExpr))
-> GenM' (ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> [ReaderT
(GarbageOpts, Gen RealWorld)
IO
(BlockDecl (Compose f Identified) (Either [Range2] CExpr))]
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(BlockDecl (Compose f Identified) (Either [Range2] CExpr))
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch ((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoDeclItem)
((forall x. GenM' x -> GenM' (Compose f Identified x))
-> GenM' (Either [Range2] CExpr)
-> [ReaderT
(GarbageOpts, Gen RealWorld)
IO
(BlockDecl (Compose f Identified) (Either [Range2] CExpr))]
forall (f :: * -> *) t.
(forall x. GenM' x -> GenM' (f x))
-> GenM' t -> [GenM' (BlockDecl f t)]
blockDeclList
((f (Identified x) -> Compose f Identified x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f (Identified x))
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Compose f Identified x)
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (Identified x) -> Compose f Identified x
forall {k} {k1} (f :: k -> *) (g :: k1 -> k) (a :: k1).
f (g a) -> Compose f g a
Compose (ReaderT (GarbageOpts, Gen RealWorld) IO (f (Identified x))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Compose f Identified x))
-> (GenM' x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f (Identified x)))
-> GenM' x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Compose f Identified x)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenM' (Identified x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f (Identified x))
forall x. GenM' x -> GenM' (f x)
f (GenM' (Identified x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f (Identified x)))
-> (GenM' x -> GenM' (Identified x))
-> GenM' x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f (Identified x))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenM' x -> GenM' (Identified x)
forall x. GenM' x -> GenM' (Identified x)
garbageIdentified)
((GarbageOpts -> Double)
-> GenM' [Range2]
-> GenM GarbageOpts CExpr
-> GenM' (Either [Range2] CExpr)
forall p a b.
(p -> Double) -> GenM p a -> GenM p b -> GenM p (Either a b)
sampleEither ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoDeclDim_Init) GenM' [Range2]
garbageDims GenM GarbageOpts CExpr
garbageCExpr))
),
(Bool
False, f Identifier -> ModGenItem f
forall (f :: * -> *). f Identifier -> ModGenItem f
MGIGenVar (f Identifier -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f Identifier)
-> GenM' (ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f Identifier)
forall x. GenM' x -> GenM' (f x)
f GenM' Identifier
garbageIdent),
( Bool
False,
Bool
-> Identifier
-> [AttrIded (TFBlockDecl Dir)]
-> MybStmt
-> ModGenItem f
forall (f :: * -> *).
Bool
-> Identifier
-> [AttrIded (TFBlockDecl Dir)]
-> MybStmt
-> ModGenItem f
MGITask (Bool
-> Identifier
-> [AttrIded (TFBlockDecl Dir)]
-> MybStmt
-> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> [AttrIded (TFBlockDecl Dir)] -> MybStmt -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoTaskFunAutomatic)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> [AttrIded (TFBlockDecl Dir)] -> MybStmt -> ModGenItem f)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
([AttrIded (TFBlockDecl Dir)] -> MybStmt -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
([AttrIded (TFBlockDecl Dir)] -> MybStmt -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [AttrIded (TFBlockDecl Dir)]
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (MybStmt -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (AttrIded (TFBlockDecl Dir))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [AttrIded (TFBlockDecl Dir)]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN
((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoTaskFunPorts)
(GenM' (TFBlockDecl Dir)
-> GenM GarbageOpts (AttrIded (TFBlockDecl Dir))
forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded (GenM' (TFBlockDecl Dir)
-> GenM GarbageOpts (AttrIded (TFBlockDecl Dir)))
-> GenM' (TFBlockDecl Dir)
-> GenM GarbageOpts (AttrIded (TFBlockDecl Dir))
forall a b. (a -> b) -> a -> b
$ GenM' Dir -> GenM' (TFBlockDecl Dir)
forall x. GenM' x -> GenM' (TFBlockDecl x)
garbageTFBlockDecl (GenM' Dir -> GenM' (TFBlockDecl Dir))
-> GenM' Dir -> GenM' (TFBlockDecl Dir)
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> CategoricalProbability) -> GenM' Dir
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM' Dir)
-> (GarbageOpts -> CategoricalProbability) -> GenM' Dir
forall a b. (a -> b) -> a -> b
$ (GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoTaskPortDirection)
ReaderT (GarbageOpts, Gen RealWorld) IO (MybStmt -> ModGenItem f)
-> GenM' MybStmt -> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MybStmt
garbageMybStmt
),
( Bool
False,
Bool
-> Maybe (ComType ())
-> Identifier
-> [AttrIded (TFBlockDecl ())]
-> FunctionStatement
-> ModGenItem f
forall (f :: * -> *).
Bool
-> Maybe (ComType ())
-> Identifier
-> [AttrIded (TFBlockDecl ())]
-> FunctionStatement
-> ModGenItem f
MGIFunc (Bool
-> Maybe (ComType ())
-> Identifier
-> [AttrIded (TFBlockDecl ())]
-> FunctionStatement
-> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (ComType ())
-> Identifier
-> [AttrIded (TFBlockDecl ())]
-> FunctionStatement
-> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoTaskFunAutomatic)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (ComType ())
-> Identifier
-> [AttrIded (TFBlockDecl ())]
-> FunctionStatement
-> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (ComType ()))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> [AttrIded (TFBlockDecl ())]
-> FunctionStatement
-> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (ComType ()))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoFunRetType) (GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
forall x. GenM' x -> GenM' (ComType x)
garbageComType (GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ()))
-> GenM' () -> ReaderT (GarbageOpts, Gen RealWorld) IO (ComType ())
forall a b. (a -> b) -> a -> b
$ () -> GenM' ()
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> [AttrIded (TFBlockDecl ())]
-> FunctionStatement
-> ModGenItem f)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
([AttrIded (TFBlockDecl ())] -> FunctionStatement -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
([AttrIded (TFBlockDecl ())] -> FunctionStatement -> ModGenItem f)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [AttrIded (TFBlockDecl ())]
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (FunctionStatement -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (NonEmpty (AttrIded (TFBlockDecl ())) -> [AttrIded (TFBlockDecl ())]
forall a. NonEmpty a -> [a]
toList
(NonEmpty (AttrIded (TFBlockDecl ()))
-> [AttrIded (TFBlockDecl ())])
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty (AttrIded (TFBlockDecl ())))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [AttrIded (TFBlockDecl ())]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (AttrIded (TFBlockDecl ()))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty (AttrIded (TFBlockDecl ())))
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageGenerateOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> NumberProbability
_ggoTaskFunPorts) (GenM' (TFBlockDecl ())
-> GenM GarbageOpts (AttrIded (TFBlockDecl ()))
forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded (GenM' (TFBlockDecl ())
-> GenM GarbageOpts (AttrIded (TFBlockDecl ())))
-> GenM' (TFBlockDecl ())
-> GenM GarbageOpts (AttrIded (TFBlockDecl ()))
forall a b. (a -> b) -> a -> b
$ GenM' () -> GenM' (TFBlockDecl ())
forall x. GenM' x -> GenM' (TFBlockDecl x)
garbageTFBlockDecl (GenM' () -> GenM' (TFBlockDecl ()))
-> GenM' () -> GenM' (TFBlockDecl ())
forall a b. (a -> b) -> a -> b
$ () -> GenM' ()
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()))
ReaderT
(GarbageOpts, Gen RealWorld) IO (FunctionStatement -> ModGenItem f)
-> GenM' FunctionStatement -> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' FunctionStatement
garbageFunctionStatement
),
(Bool
False, f ParamOver -> ModGenItem f
forall (f :: * -> *). f ParamOver -> ModGenItem f
MGIDefParam (f ParamOver -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f ParamOver)
-> GenM' (ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ParamOver
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f ParamOver)
forall x. GenM' x -> GenM' (f x)
f (HierIdent -> CMinTypMax -> ParamOver
ParamOver (HierIdent -> CMinTypMax -> ParamOver)
-> GenM' HierIdent
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> ParamOver)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' HierIdent
garbageHierIdent ReaderT (GarbageOpts, Gen RealWorld) IO (CMinTypMax -> ParamOver)
-> GenM' CMinTypMax -> GenM' ParamOver
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax)),
(Bool
False, DriveStrength -> Maybe Delay3 -> f NetAssign -> ModGenItem f
forall (f :: * -> *).
DriveStrength -> Maybe Delay3 -> f NetAssign -> ModGenItem f
MGIContAss (DriveStrength -> Maybe Delay3 -> f NetAssign -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f NetAssign -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' DriveStrength
garbageDriveStrength ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay3 -> f NetAssign -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f NetAssign -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3 ReaderT
(GarbageOpts, Gen RealWorld) IO (f NetAssign -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetAssign)
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetAssign
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f NetAssign)
forall x. GenM' x -> GenM' (f x)
f GenM' NetAssign
garbageNetAssign),
(Bool
False, (forall x. GenM' x -> GenM' (f x)) -> GenM' (ModGenItem f)
forall (f :: * -> *).
(forall x. GenM' x -> GenM' (f x)) -> GenM' (ModGenItem f)
garbageGateInst GenM' x -> GenM' (f x)
forall x. GenM' x -> GenM' (f x)
f),
( Bool
False,
Identifier
-> DriveStrength -> Maybe Delay2 -> f UDPInst -> ModGenItem f
forall (f :: * -> *).
Identifier
-> DriveStrength -> Maybe Delay2 -> f UDPInst -> ModGenItem f
MGIUDPInst (Identifier
-> DriveStrength -> Maybe Delay2 -> f UDPInst -> ModGenItem f)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> Maybe Delay2 -> f UDPInst -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(DriveStrength -> Maybe Delay2 -> f UDPInst -> ModGenItem f)
-> GenM' DriveStrength
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f UDPInst -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' DriveStrength
garbageDriveStrength
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Delay2 -> f UDPInst -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f UDPInst -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2
ReaderT (GarbageOpts, Gen RealWorld) IO (f UDPInst -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f UDPInst)
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' UDPInst
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f UDPInst)
forall x. GenM' x -> GenM' (f x)
f
( Maybe InstanceName -> NetLValue -> NonEmpty Expr -> UDPInst
UDPInst
(Maybe InstanceName -> NetLValue -> NonEmpty Expr -> UDPInst)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NonEmpty Expr -> UDPInst)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> GenM' InstanceName
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe InstanceName)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoPrimitiveOptIdent) GenM' InstanceName
garbageInstanceName
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NetLValue -> NonEmpty Expr -> UDPInst)
-> GenM' NetLValue
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty Expr -> UDPInst)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' NetLValue
garbageNetLV
ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr -> UDPInst)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
-> GenM' UDPInst
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Expr)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE (GarbagePrimitiveOpts -> NumberProbability
_gpoPorts (GarbagePrimitiveOpts -> NumberProbability)
-> (GarbageOpts -> GarbagePrimitiveOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbagePrimitiveOpts
_goPrimitive) GenM' Expr
garbageExpr
)
),
( Bool
False,
Identifier -> ParamAssign -> f ModInst -> ModGenItem f
forall (f :: * -> *).
Identifier -> ParamAssign -> f ModInst -> ModGenItem f
MGIModInst (Identifier -> ParamAssign -> f ModInst -> ModGenItem f)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(ParamAssign -> f ModInst -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(ParamAssign -> f ModInst -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO ParamAssign
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (f ModInst -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO ParamAssign
-> ReaderT (GarbageOpts, Gen RealWorld) IO ParamAssign
-> ReaderT (GarbageOpts, Gen RealWorld) IO ParamAssign
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbageModuleOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Double
_gmoNamed_Positional)
( [Identified (Maybe MinTypMax)] -> ParamAssign
ParamNamed ([Identified (Maybe MinTypMax)] -> ParamAssign)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [Identified (Maybe MinTypMax)]
-> ReaderT (GarbageOpts, Gen RealWorld) IO ParamAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (Identified (Maybe MinTypMax))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [Identified (Maybe MinTypMax)]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN
((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoParameters)
(GenM' (Maybe MinTypMax)
-> GenM GarbageOpts (Identified (Maybe MinTypMax))
forall x. GenM' x -> GenM' (Identified x)
garbageIdentified (GenM' (Maybe MinTypMax)
-> GenM GarbageOpts (Identified (Maybe MinTypMax)))
-> GenM' (Maybe MinTypMax)
-> GenM GarbageOpts (Identified (Maybe MinTypMax))
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> Double)
-> GenM' MinTypMax -> GenM' (Maybe MinTypMax)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageModuleOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Double
_gmoOptionalParameter) GenM' MinTypMax
garbageMinTypMax)
)
([Expr] -> ParamAssign
ParamPositional ([Expr] -> ParamAssign)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Expr]
-> ReaderT (GarbageOpts, Gen RealWorld) IO ParamAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM' Expr -> ReaderT (GarbageOpts, Gen RealWorld) IO [Expr]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoParameters) GenM' Expr
garbageExpr)
ReaderT (GarbageOpts, Gen RealWorld) IO (f ModInst -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f ModInst)
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' ModInst
-> ReaderT (GarbageOpts, Gen RealWorld) IO (f ModInst)
forall x. GenM' x -> GenM' (f x)
f (InstanceName -> PortAssign -> ModInst
ModInst (InstanceName -> PortAssign -> ModInst)
-> GenM' InstanceName
-> ReaderT (GarbageOpts, Gen RealWorld) IO (PortAssign -> ModInst)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' InstanceName
garbageInstanceName
ReaderT (GarbageOpts, Gen RealWorld) IO (PortAssign -> ModInst)
-> ReaderT (GarbageOpts, Gen RealWorld) IO PortAssign
-> GenM' ModInst
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO PortAssign
-> ReaderT (GarbageOpts, Gen RealWorld) IO PortAssign
-> ReaderT (GarbageOpts, Gen RealWorld) IO PortAssign
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbageModuleOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Double
_gmoNamed_Positional)
([AttrIded (Maybe Expr)] -> PortAssign
PortNamed ([AttrIded (Maybe Expr)] -> PortAssign)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded (Maybe Expr)]
-> ReaderT (GarbageOpts, Gen RealWorld) IO PortAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (AttrIded (Maybe Expr))
-> ReaderT (GarbageOpts, Gen RealWorld) IO [AttrIded (Maybe Expr)]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoPorts) (GenM GarbageOpts (Maybe Expr)
-> GenM GarbageOpts (AttrIded (Maybe Expr))
forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded GenM GarbageOpts (Maybe Expr)
optexpr))
([Attributed (Maybe Expr)] -> PortAssign
PortPositional ([Attributed (Maybe Expr)] -> PortAssign)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [Attributed (Maybe Expr)]
-> ReaderT (GarbageOpts, Gen RealWorld) IO PortAssign
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (Attributed (Maybe Expr))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO [Attributed (Maybe Expr)]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoPorts) (GenM GarbageOpts (Maybe Expr)
-> GenM GarbageOpts (Attributed (Maybe Expr))
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed GenM GarbageOpts (Maybe Expr)
optexpr)))
),
(Bool
False, AttrStmt -> ModGenItem f
forall (f :: * -> *). AttrStmt -> ModGenItem f
MGIInitial (AttrStmt -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
-> GenM' (ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
garbageAttrStmt),
(Bool
False, AttrStmt -> ModGenItem f
forall (f :: * -> *). AttrStmt -> ModGenItem f
MGIAlways (AttrStmt -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
-> GenM' (ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO AttrStmt
garbageAttrStmt),
( Bool
True,
Identifier
-> CExpr
-> CExpr
-> Identifier
-> CExpr
-> GenerateBlock
-> ModGenItem f
forall (f :: * -> *).
Identifier
-> CExpr
-> CExpr
-> Identifier
-> CExpr
-> GenerateBlock
-> ModGenItem f
MGILoopGen (Identifier
-> CExpr
-> CExpr
-> Identifier
-> CExpr
-> GenerateBlock
-> ModGenItem f)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CExpr
-> CExpr -> Identifier -> CExpr -> GenerateBlock -> ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CExpr
-> CExpr -> Identifier -> CExpr -> GenerateBlock -> ModGenItem f)
-> GenM GarbageOpts CExpr
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CExpr -> Identifier -> CExpr -> GenerateBlock -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts CExpr
garbageCExpr
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CExpr -> Identifier -> CExpr -> GenerateBlock -> ModGenItem f)
-> GenM GarbageOpts CExpr
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier -> CExpr -> GenerateBlock -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts CExpr
garbageCExpr
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier -> CExpr -> GenerateBlock -> ModGenItem f)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CExpr -> GenerateBlock -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CExpr -> GenerateBlock -> ModGenItem f)
-> GenM GarbageOpts CExpr
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenerateBlock -> ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts CExpr
garbageCExpr
ReaderT
(GarbageOpts, Gen RealWorld) IO (GenerateBlock -> ModGenItem f)
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
-> GenM' (ModGenItem f)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
garbageGenerateBlock
),
(Bool
True, ModGenCondItem -> ModGenItem f
forall (f :: * -> *). ModGenCondItem -> ModGenItem f
MGICondItem (ModGenCondItem -> ModGenItem f)
-> GenM' ModGenCondItem -> GenM' (ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ModGenCondItem
garbageGenIf),
(Bool
True, ModGenCondItem -> ModGenItem f
forall (f :: * -> *). ModGenCondItem -> ModGenItem f
MGICondItem (ModGenCondItem -> ModGenItem f)
-> GenM' ModGenCondItem -> GenM' (ModGenItem f)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ModGenCondItem
garbageGenCase)
]
where
g :: (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> c
x = GarbageGenerateOpts -> c
x (GarbageGenerateOpts -> c)
-> (GarbageOpts -> GarbageGenerateOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate
m :: (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> c
x = GarbageModuleOpts -> c
x (GarbageModuleOpts -> c)
-> (GarbageOpts -> GarbageModuleOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageModuleOpts
_goModule
optd3 :: ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3 = (GarbageOpts -> Double)
-> GenM GarbageOpts Delay3
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoInstOptionalDelay) GenM GarbageOpts Delay3
garbageDelay3
optd2 :: ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
optd2 = (GarbageOpts -> Double)
-> GenM GarbageOpts Delay2
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay2)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoInstOptionalDelay) GenM GarbageOpts Delay2
garbageDelay2
optexpr :: GenM GarbageOpts (Maybe Expr)
optexpr = (GarbageOpts -> Double)
-> GenM' Expr -> GenM GarbageOpts (Maybe Expr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageModuleOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Double
_gmoOptionalPort) GenM' Expr
garbageExpr
optblock :: GenM GarbageOpts (Maybe GenerateBlock)
optblock = (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
-> GenM GarbageOpts (Maybe GenerateBlock)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoOptionalBlock) ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
garbageGenerateBlock
gnetprop :: ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
gnetprop = Bool -> Maybe (Maybe Bool, Range2) -> Maybe Delay3 -> NetProp
NetProp (Bool -> Maybe (Maybe Bool, Range2) -> Maybe Delay3 -> NetProp)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Maybe Bool, Range2) -> Maybe Delay3 -> NetProp)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli (GarbageTypeOpts -> Double
_gtoConcreteSignedness (GarbageTypeOpts -> Double)
-> (GarbageOpts -> GarbageTypeOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageTypeOpts
_goType)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Maybe Bool, Range2) -> Maybe Delay3 -> NetProp)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe (Maybe Bool, Range2))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe Delay3 -> NetProp)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM GarbageOpts (Maybe Bool, Range2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe (Maybe Bool, Range2))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageGenerateOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> Double
_ggoNetRange)
(ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
-> GenM' Range2 -> GenM GarbageOpts (Maybe Bool, Range2)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair ((GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p (Maybe a)
sampleMaybeEnum ((GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool))
-> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ (GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoNetVectoring) GenM' Range2
garbageRange2)
ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3 -> NetProp)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
-> ReaderT (GarbageOpts, Gen RealWorld) IO NetProp
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Delay3)
optd3
gnetdecl :: GenM' NetDecl
gnetdecl = Identifier -> [Range2] -> NetDecl
NetDecl (Identifier -> [Range2] -> NetDecl)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO ([Range2] -> NetDecl)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent ReaderT (GarbageOpts, Gen RealWorld) IO ([Range2] -> NetDecl)
-> GenM' [Range2] -> GenM' NetDecl
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' [Range2]
garbageDims
gnetinit :: GenM' NetInit
gnetinit = Identifier -> Expr -> NetInit
NetInit (Identifier -> Expr -> NetInit)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> NetInit)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent ReaderT (GarbageOpts, Gen RealWorld) IO (Expr -> NetInit)
-> GenM' Expr -> GenM' NetInit
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr
garbageModGenBlockedItem :: GenM' (Attributed ModGenBlockedItem)
garbageModGenBlockedItem :: GenM' (Attributed ModGenBlockedItem)
garbageModGenBlockedItem = GenM' ModGenBlockedItem -> GenM' (Attributed ModGenBlockedItem)
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed (GenM' ModGenBlockedItem -> GenM' (Attributed ModGenBlockedItem))
-> GenM' ModGenBlockedItem -> GenM' (Attributed ModGenBlockedItem)
forall a b. (a -> b) -> a -> b
$ (forall x. GenM' x -> GenM' (Identity x))
-> GenM' ModGenBlockedItem
forall (f :: * -> *).
(forall x. GenM' x -> GenM' (f x)) -> GenM' (ModGenItem f)
garbageModGenItem ((forall x. GenM' x -> GenM' (Identity x))
-> GenM' ModGenBlockedItem)
-> (forall x. GenM' x -> GenM' (Identity x))
-> GenM' ModGenBlockedItem
forall a b. (a -> b) -> a -> b
$ (x -> Identity x)
-> ReaderT (GarbageOpts, Gen RealWorld) IO x
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity x)
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap x -> Identity x
forall a. a -> Identity a
Identity
garbageGenerateBlock :: GenM' GenerateBlock
garbageGenerateBlock :: ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
garbageGenerateBlock =
GenM' [Attributed ModGenBlockedItem]
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
forall x. GenM' x -> GenM' (Identified x)
garbageIdentified (GenM' [Attributed ModGenBlockedItem]
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock)
-> GenM' [Attributed ModGenBlockedItem]
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> NumberProbability)
-> GenM' (Attributed ModGenBlockedItem)
-> GenM' [Attributed ModGenBlockedItem]
forall a.
(GarbageOpts -> NumberProbability) -> GenM' a -> GenM' [a]
repeatModGenRecursive (GarbageGenerateOpts -> NumberProbability
_ggoItems (GarbageGenerateOpts -> NumberProbability)
-> (GarbageOpts -> GarbageGenerateOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate) (GenM' (Attributed ModGenBlockedItem)
-> GenM' [Attributed ModGenBlockedItem])
-> GenM' (Attributed ModGenBlockedItem)
-> GenM' [Attributed ModGenBlockedItem]
forall a b. (a -> b) -> a -> b
$ GenM' (Attributed ModGenBlockedItem)
garbageModGenBlockedItem
garbageGenCondBlock :: GenM' GenerateCondBlock
garbageGenCondBlock :: GenM' GenerateCondBlock
garbageGenCondBlock =
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' GenerateCondBlock)
-> GenM' GenerateCondBlock
forall a.
(GarbageOpts -> GarbageAttenuationOpts)
-> (GarbageOpts -> CategoricalProbability)
-> NonEmpty (Bool, GenM' a)
-> GenM' a
sampleAttenuatedBranch
((GarbageGenerateOpts -> GarbageAttenuationOpts)
-> GarbageOpts -> GarbageAttenuationOpts
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> GarbageAttenuationOpts
_ggoAttenuation)
((GarbageGenerateOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> CategoricalProbability
_ggoCondBlock)
[ (Bool
False, GenerateCondBlock -> GenM' GenerateCondBlock
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure GenerateCondBlock
GCBEmpty),
(Bool
True, GenerateBlock -> GenerateCondBlock
GCBBlock (GenerateBlock -> GenerateCondBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
-> GenM' GenerateCondBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO GenerateBlock
garbageGenerateBlock),
(Bool
True, Attributed ModGenCondItem -> GenerateCondBlock
GCBConditional (Attributed ModGenCondItem -> GenerateCondBlock)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Attributed ModGenCondItem)
-> GenM' GenerateCondBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ModGenCondItem
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Attributed ModGenCondItem)
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed GenM' ModGenCondItem
garbageGenIf),
(Bool
True, Attributed ModGenCondItem -> GenerateCondBlock
GCBConditional (Attributed ModGenCondItem -> GenerateCondBlock)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Attributed ModGenCondItem)
-> GenM' GenerateCondBlock
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' ModGenCondItem
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Attributed ModGenCondItem)
forall x. GenM' x -> GenM' (Attributed x)
garbageAttributed GenM' ModGenCondItem
garbageGenCase)
]
where g :: (GarbageGenerateOpts -> c) -> GarbageOpts -> c
g GarbageGenerateOpts -> c
x = GarbageGenerateOpts -> c
x (GarbageGenerateOpts -> c)
-> (GarbageOpts -> GarbageGenerateOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate
garbageSpecTerm :: GenM' SpecTerm
garbageSpecTerm :: GenM' SpecTerm
garbageSpecTerm =
Identifier -> Maybe CRangeExpr -> SpecTerm
SpecTerm (Identifier -> Maybe CRangeExpr -> SpecTerm)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CRangeExpr -> SpecTerm)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CRangeExpr -> SpecTerm)
-> GenM' (Maybe CRangeExpr) -> GenM' SpecTerm
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM GarbageOpts CRangeExpr -> GenM' (Maybe CRangeExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageSpecifyOpts -> Double
_gsyoTermRange (GarbageSpecifyOpts -> Double)
-> (GarbageOpts -> GarbageSpecifyOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageSpecifyOpts
_goSpecify) GenM GarbageOpts CRangeExpr
garbageCRangeExpr
garbagePPIdentifier :: GenM' Identifier
garbagePPIdentifier :: GenM' Identifier
garbagePPIdentifier =
ByteString -> Identifier
Identifier (ByteString -> Identifier) -> GenM' ByteString -> GenM' Identifier
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> GenM' ByteString -> GenM' ByteString -> GenM' ByteString
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice (GarbageSpecifyOpts -> Double
_gsyoPathPulseEscaped_Simple (GarbageSpecifyOpts -> Double)
-> (GarbageOpts -> GarbageSpecifyOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageSpecifyOpts
_goSpecify) GenM' ByteString
garbageEscapedBS GenM' ByteString
garbageSimpleBS
garbagePPTerm :: GenM' SpecTerm
garbagePPTerm :: GenM' SpecTerm
garbagePPTerm =
Identifier -> Maybe CRangeExpr -> SpecTerm
SpecTerm (Identifier -> Maybe CRangeExpr -> SpecTerm)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CRangeExpr -> SpecTerm)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbagePPIdentifier
ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CRangeExpr -> SpecTerm)
-> GenM' (Maybe CRangeExpr) -> GenM' SpecTerm
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM GarbageOpts CRangeExpr -> GenM' (Maybe CRangeExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageSpecifyOpts -> Double
_gsyoPathPulseRange (GarbageSpecifyOpts -> Double)
-> (GarbageOpts -> GarbageSpecifyOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageSpecifyOpts
_goSpecify) GenM GarbageOpts CRangeExpr
garbageCRangeExpr
garbageSPRange :: GenM' (Maybe Range2)
garbageSPRange :: ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
garbageSPRange = (GarbageOpts -> Double)
-> GenM' Range2
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe (GarbageSpecifyOpts -> Double
_gsyoParamRange (GarbageSpecifyOpts -> Double)
-> (GarbageOpts -> GarbageSpecifyOpts) -> GarbageOpts -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageSpecifyOpts
_goSpecify) GenM' Range2
garbageRange2
garbageSpecParamAssign :: GenM' SpecParamDecl
garbageSpecParamAssign :: GenM' SpecParamDecl
garbageSpecParamAssign = Identifier -> CMinTypMax -> SpecParamDecl
SPDAssign (Identifier -> CMinTypMax -> SpecParamDecl)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> SpecParamDecl)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> SpecParamDecl)
-> GenM' CMinTypMax -> GenM' SpecParamDecl
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
garbageNoPathPulse :: GenM' SpecParamDecl
garbageNoPathPulse :: GenM' SpecParamDecl
garbageNoPathPulse = Maybe (SpecTerm, SpecTerm)
-> CMinTypMax -> CMinTypMax -> SpecParamDecl
SPDPathPulse Maybe (SpecTerm, SpecTerm)
forall a. Maybe a
Nothing (CMinTypMax -> CMinTypMax -> SpecParamDecl)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> SpecParamDecl)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' CMinTypMax
garbageCMinTypMax ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> SpecParamDecl)
-> GenM' CMinTypMax -> GenM' SpecParamDecl
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
garbagePathPulse :: GenM' SpecParamDecl
garbagePathPulse :: GenM' SpecParamDecl
garbagePathPulse =
Maybe (SpecTerm, SpecTerm)
-> CMinTypMax -> CMinTypMax -> SpecParamDecl
SPDPathPulse (Maybe (SpecTerm, SpecTerm)
-> CMinTypMax -> CMinTypMax -> SpecParamDecl)
-> ((SpecTerm, SpecTerm) -> Maybe (SpecTerm, SpecTerm))
-> (SpecTerm, SpecTerm)
-> CMinTypMax
-> CMinTypMax
-> SpecParamDecl
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SpecTerm, SpecTerm) -> Maybe (SpecTerm, SpecTerm)
forall a. a -> Maybe a
Just ((SpecTerm, SpecTerm) -> CMinTypMax -> CMinTypMax -> SpecParamDecl)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (SpecTerm, SpecTerm)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> SpecParamDecl)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' SpecTerm
-> GenM' SpecTerm
-> ReaderT (GarbageOpts, Gen RealWorld) IO (SpecTerm, SpecTerm)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair GenM' SpecTerm
garbagePPTerm GenM' SpecTerm
garbagePPTerm
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> SpecParamDecl)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> SpecParamDecl)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> SpecParamDecl)
-> GenM' CMinTypMax -> GenM' SpecParamDecl
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
garbageSpecifyItem :: GenM' SpecifyBlockedItem
garbageSpecifyItem :: GenM GarbageOpts SpecifyBlockedItem
garbageSpecifyItem =
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts SpecifyBlockedItem]
-> GenM GarbageOpts SpecifyBlockedItem
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageSpecifyOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
s GarbageSpecifyOpts -> CategoricalProbability
_gsyoItem)
[ Maybe Range2 -> Identity SpecParamDecl -> SpecifyBlockedItem
forall (f :: * -> *).
Maybe Range2 -> f SpecParamDecl -> SpecifyItem f
SISpecParam (Maybe Range2 -> Identity SpecParamDecl -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identity SpecParamDecl -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
garbageSPRange ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identity SpecParamDecl -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecParamDecl)
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (SpecParamDecl -> Identity SpecParamDecl)
-> GenM' SpecParamDecl
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecParamDecl)
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SpecParamDecl -> Identity SpecParamDecl
forall a. a -> Identity a
Identity GenM' SpecParamDecl
garbageSpecParamAssign,
Maybe Range2 -> Identity SpecParamDecl -> SpecifyBlockedItem
forall (f :: * -> *).
Maybe Range2 -> f SpecParamDecl -> SpecifyItem f
SISpecParam (Maybe Range2 -> Identity SpecParamDecl -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identity SpecParamDecl -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
garbageSPRange ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identity SpecParamDecl -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecParamDecl)
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (SpecParamDecl -> Identity SpecParamDecl)
-> GenM' SpecParamDecl
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecParamDecl)
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SpecParamDecl -> Identity SpecParamDecl
forall a. a -> Identity a
Identity GenM' SpecParamDecl
garbageNoPathPulse,
Maybe Range2 -> Identity SpecParamDecl -> SpecifyBlockedItem
forall (f :: * -> *).
Maybe Range2 -> f SpecParamDecl -> SpecifyItem f
SISpecParam (Maybe Range2 -> Identity SpecParamDecl -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identity SpecParamDecl -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
garbageSPRange ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identity SpecParamDecl -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecParamDecl)
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (SpecParamDecl -> Identity SpecParamDecl)
-> GenM' SpecParamDecl
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecParamDecl)
forall a b.
(a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SpecParamDecl -> Identity SpecParamDecl
forall a. a -> Identity a
Identity GenM' SpecParamDecl
garbagePathPulse,
Identity SpecTerm -> SpecifyBlockedItem
forall (f :: * -> *). f SpecTerm -> SpecifyItem f
SIPulsestyleOnevent (Identity SpecTerm -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
gst,
Identity SpecTerm -> SpecifyBlockedItem
forall (f :: * -> *). f SpecTerm -> SpecifyItem f
SIPulsestyleOndetect (Identity SpecTerm -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
gst,
Identity SpecTerm -> SpecifyBlockedItem
forall (f :: * -> *). f SpecTerm -> SpecifyItem f
SIShowcancelled (Identity SpecTerm -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
gst,
Identity SpecTerm -> SpecifyBlockedItem
forall (f :: * -> *). f SpecTerm -> SpecifyItem f
SINoshowcancelled (Identity SpecTerm -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
gst,
do
ModulePathCondition
cond <- (GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts ModulePathCondition]
-> GenM GarbageOpts ModulePathCondition
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageSpecifyPathOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> CategoricalProbability
_gspoCondition)
[ ModulePathCondition -> GenM GarbageOpts ModulePathCondition
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ModulePathCondition
MPCNone,
ModulePathCondition -> GenM GarbageOpts ModulePathCondition
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ModulePathCondition
MPCAlways,
GenExpr Identifier () Attributes -> ModulePathCondition
MPCCond (GenExpr Identifier () Attributes -> ModulePathCondition)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenExpr Identifier () Attributes)
-> GenM GarbageOpts ModulePathCondition
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
-> Bool
-> GenM' ()
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (GenExpr Identifier () Attributes)
forall i r a.
GenM' i -> Bool -> GenM' r -> GenM' a -> GenM' (GenExpr i r a)
garbageGenExpr GenM' Identifier
garbageIdent Bool
False (() -> GenM' ()
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) GenM' Attributes
garbageAttributes
]
SpecPath
conn <- (GarbageOpts -> Double)
-> GenM GarbageOpts SpecPath
-> GenM GarbageOpts SpecPath
-> GenM GarbageOpts SpecPath
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbageSpecifyPathOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> Double
_gspoFull_Parallel)
( NonEmpty SpecTerm -> NonEmpty SpecTerm -> SpecPath
SPFull (NonEmpty SpecTerm -> NonEmpty SpecTerm -> SpecPath)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SpecTerm)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty SpecTerm -> SpecPath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM' SpecTerm
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SpecTerm)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageSpecifyPathOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> NumberProbability
_gspoFullSources) GenM' SpecTerm
garbageSpecTerm
ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty SpecTerm -> SpecPath)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SpecTerm)
-> GenM GarbageOpts SpecPath
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' SpecTerm
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SpecTerm)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbageSpecifyPathOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> NumberProbability
_gspoFullDestinations) GenM' SpecTerm
garbageSpecTerm
)
(SpecTerm -> SpecTerm -> SpecPath
SPParallel (SpecTerm -> SpecTerm -> SpecPath)
-> GenM' SpecTerm
-> ReaderT (GarbageOpts, Gen RealWorld) IO (SpecTerm -> SpecPath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' SpecTerm
garbageSpecTerm ReaderT (GarbageOpts, Gen RealWorld) IO (SpecTerm -> SpecPath)
-> GenM' SpecTerm -> GenM GarbageOpts SpecPath
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' SpecTerm
garbageSpecTerm)
Maybe Bool
pol <- (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p (Maybe a)
sampleMaybeEnum ((GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool))
-> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ (GarbageSpecifyPathOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> CategoricalProbability
_gspoPolarity
Maybe (Expr, Maybe Bool)
eds <- (GarbageOpts -> Double)
-> GenM GarbageOpts (Expr, Maybe Bool)
-> GenM GarbageOpts (Maybe (Expr, Maybe Bool))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyPathOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> Double
_gspoEdgeSensitive) (GenM GarbageOpts (Expr, Maybe Bool)
-> GenM GarbageOpts (Maybe (Expr, Maybe Bool)))
-> GenM GarbageOpts (Expr, Maybe Bool)
-> GenM GarbageOpts (Maybe (Expr, Maybe Bool))
forall a b. (a -> b) -> a -> b
$
GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
-> GenM GarbageOpts (Expr, Maybe Bool)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair GenM' Expr
garbageExpr (ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
-> GenM GarbageOpts (Expr, Maybe Bool))
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
-> GenM GarbageOpts (Expr, Maybe Bool)
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p (Maybe a)
sampleMaybeEnum ((GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool))
-> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
forall a b. (a -> b) -> a -> b
$ (GarbageSpecifyPathOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> CategoricalProbability
_gspoEdgeSensitivity
PathDelayValue
pdv <- (GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts PathDelayValue]
-> GenM GarbageOpts PathDelayValue
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageSpecifyPathOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> CategoricalProbability
_gspoDelayKind)
[ CMinTypMax -> PathDelayValue
PDV1 (CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax -> GenM GarbageOpts PathDelayValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' CMinTypMax
garbageCMinTypMax,
CMinTypMax -> CMinTypMax -> PathDelayValue
PDV2 (CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' CMinTypMax
garbageCMinTypMax ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax -> GenM GarbageOpts PathDelayValue
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax,
CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue
PDV3 (CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> PathDelayValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' CMinTypMax
garbageCMinTypMax ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax -> GenM GarbageOpts PathDelayValue
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax,
CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue
PDV6 (CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax -> GenM GarbageOpts PathDelayValue
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax,
CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue
PDV12 (CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> CMinTypMax
-> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax
-> CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(CMinTypMax -> CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld) IO (CMinTypMax -> PathDelayValue)
-> GenM' CMinTypMax -> GenM GarbageOpts PathDelayValue
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' CMinTypMax
garbageCMinTypMax
]
SpecifyBlockedItem -> GenM GarbageOpts SpecifyBlockedItem
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SpecifyBlockedItem -> GenM GarbageOpts SpecifyBlockedItem)
-> SpecifyBlockedItem -> GenM GarbageOpts SpecifyBlockedItem
forall a b. (a -> b) -> a -> b
$ ModulePathCondition
-> SpecPath
-> Maybe Bool
-> Maybe (Expr, Maybe Bool)
-> PathDelayValue
-> SpecifyBlockedItem
forall (f :: * -> *).
ModulePathCondition
-> SpecPath
-> Maybe Bool
-> Maybe (Expr, Maybe Bool)
-> PathDelayValue
-> SpecifyItem f
SIPathDeclaration ModulePathCondition
cond SpecPath
conn Maybe Bool
pol Maybe (Expr, Maybe Bool)
eds PathDelayValue
pdv,
STCArgs -> SpecifyBlockedItem
forall (f :: * -> *). STCArgs -> SpecifyItem f
SISetup (STCArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca,
STCArgs -> SpecifyBlockedItem
forall (f :: * -> *). STCArgs -> SpecifyItem f
SIHold (STCArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca,
STCArgs -> STCAddArgs -> SpecifyBlockedItem
forall (f :: * -> *). STCArgs -> STCAddArgs -> SpecifyItem f
SISetupHold (STCArgs -> STCAddArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (STCAddArgs -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca ReaderT
(GarbageOpts, Gen RealWorld) IO (STCAddArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCAddArgs
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO STCAddArgs
gstcaa,
STCArgs -> SpecifyBlockedItem
forall (f :: * -> *). STCArgs -> SpecifyItem f
SIRecovery (STCArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca,
STCArgs -> SpecifyBlockedItem
forall (f :: * -> *). STCArgs -> SpecifyItem f
SIRemoval (STCArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca,
STCArgs -> STCAddArgs -> SpecifyBlockedItem
forall (f :: * -> *). STCArgs -> STCAddArgs -> SpecifyItem f
SIRecrem (STCArgs -> STCAddArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (STCAddArgs -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca ReaderT
(GarbageOpts, Gen RealWorld) IO (STCAddArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCAddArgs
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO STCAddArgs
gstcaa,
STCArgs -> SpecifyBlockedItem
forall (f :: * -> *). STCArgs -> SpecifyItem f
SISkew (STCArgs -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> GenM GarbageOpts SpecifyBlockedItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca,
STCArgs -> Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem
forall (f :: * -> *).
STCArgs -> Maybe CExpr -> Maybe CExpr -> SpecifyItem f
SITimeSkew (STCArgs -> Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CExpr -> SpecifyBlockedItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
gmce ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CExpr -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
gmce,
STCArgs -> Expr -> Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem
forall (f :: * -> *).
STCArgs -> Expr -> Maybe CExpr -> Maybe CExpr -> SpecifyItem f
SIFullSkew (STCArgs
-> Expr -> Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe CExpr -> Maybe CExpr -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CExpr -> SpecifyBlockedItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
gmce ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe CExpr -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
gmce,
ControlledTimingCheckEvent
-> Expr -> Maybe Identifier -> SpecifyBlockedItem
forall (f :: * -> *).
ControlledTimingCheckEvent
-> Expr -> Maybe Identifier -> SpecifyItem f
SIPeriod (ControlledTimingCheckEvent
-> Expr -> Maybe Identifier -> SpecifyBlockedItem)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ControlledTimingCheckEvent
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> Maybe Identifier -> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO ControlledTimingCheckEvent
gctce ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> Maybe Identifier -> SpecifyBlockedItem)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Identifier -> SpecifyBlockedItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Identifier -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) GenM' Identifier
garbageIdent,
do
(Maybe CExpr
me, Maybe Identifier
i) <- (GarbageOpts -> Double)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) ((Maybe CExpr, Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe CExpr
forall a. Maybe a
Nothing, Maybe Identifier
forall a. Maybe a
Nothing)) (GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier))
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
forall a b. (a -> b) -> a -> b
$
ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair (CExpr -> Maybe CExpr
forall a. a -> Maybe a
Just (CExpr -> Maybe CExpr)
-> GenM GarbageOpts CExpr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts CExpr
garbageCExpr) (ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier))
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
-> GenM GarbageOpts (Maybe CExpr, Maybe Identifier)
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> Double)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) GenM' Identifier
garbageIdent
ControlledTimingCheckEvent
cre <- ReaderT (GarbageOpts, Gen RealWorld) IO ControlledTimingCheckEvent
gctce
Expr
tcl <- GenM' Expr
garbageExpr
SpecifyBlockedItem -> GenM GarbageOpts SpecifyBlockedItem
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (SpecifyBlockedItem -> GenM GarbageOpts SpecifyBlockedItem)
-> SpecifyBlockedItem -> GenM GarbageOpts SpecifyBlockedItem
forall a b. (a -> b) -> a -> b
$ ControlledTimingCheckEvent
-> Expr -> Maybe CExpr -> Maybe Identifier -> SpecifyBlockedItem
forall (f :: * -> *).
ControlledTimingCheckEvent
-> Expr -> Maybe CExpr -> Maybe Identifier -> SpecifyItem f
SIWidth ControlledTimingCheckEvent
cre Expr
tcl Maybe CExpr
me Maybe Identifier
i,
TimingCheckEvent
-> TimingCheckEvent
-> MinTypMax
-> MinTypMax
-> Maybe Identifier
-> SpecifyBlockedItem
forall (f :: * -> *).
TimingCheckEvent
-> TimingCheckEvent
-> MinTypMax
-> MinTypMax
-> Maybe Identifier
-> SpecifyItem f
SINoChange (TimingCheckEvent
-> TimingCheckEvent
-> MinTypMax
-> MinTypMax
-> Maybe Identifier
-> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(TimingCheckEvent
-> MinTypMax
-> MinTypMax
-> Maybe Identifier
-> SpecifyBlockedItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
gtce
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(TimingCheckEvent
-> MinTypMax
-> MinTypMax
-> Maybe Identifier
-> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(MinTypMax -> MinTypMax -> Maybe Identifier -> SpecifyBlockedItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
gtce
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(MinTypMax -> MinTypMax -> Maybe Identifier -> SpecifyBlockedItem)
-> GenM' MinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(MinTypMax -> Maybe Identifier -> SpecifyBlockedItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MinTypMax
garbageMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(MinTypMax -> Maybe Identifier -> SpecifyBlockedItem)
-> GenM' MinTypMax
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Identifier -> SpecifyBlockedItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' MinTypMax
garbageMinTypMax
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Identifier -> SpecifyBlockedItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
-> GenM GarbageOpts SpecifyBlockedItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) GenM' Identifier
garbageIdent
]
where
s :: (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
s GarbageSpecifyOpts -> c
x = GarbageSpecifyOpts -> c
x (GarbageSpecifyOpts -> c)
-> (GarbageOpts -> GarbageSpecifyOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageSpecifyOpts
_goSpecify
p :: (GarbageSpecifyPathOpts -> c) -> GarbageOpts -> c
p GarbageSpecifyPathOpts -> c
x = (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
forall {c}. (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
s ((GarbageSpecifyOpts -> c) -> GarbageOpts -> c)
-> (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
forall a b. (a -> b) -> a -> b
$ GarbageSpecifyPathOpts -> c
x (GarbageSpecifyPathOpts -> c)
-> (GarbageSpecifyOpts -> GarbageSpecifyPathOpts)
-> GarbageSpecifyOpts
-> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageSpecifyOpts -> GarbageSpecifyPathOpts
_gsyoPath
t :: (GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> c
x = (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
forall {c}. (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
s ((GarbageSpecifyOpts -> c) -> GarbageOpts -> c)
-> (GarbageSpecifyOpts -> c) -> GarbageOpts -> c
forall a b. (a -> b) -> a -> b
$ GarbageSpecifyTimingCheckOpts -> c
x (GarbageSpecifyTimingCheckOpts -> c)
-> (GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts)
-> GarbageSpecifyOpts
-> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts
_gsyoTimingCheck
gst :: ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
gst = SpecTerm -> Identity SpecTerm
forall a. a -> Identity a
Identity (SpecTerm -> Identity SpecTerm)
-> GenM' SpecTerm
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Identity SpecTerm)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' SpecTerm
garbageSpecTerm
gmce :: ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
gmce = (GarbageOpts -> Double)
-> GenM GarbageOpts CExpr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) GenM GarbageOpts CExpr
garbageCExpr
gtcc :: ReaderT (GarbageOpts, Gen RealWorld) IO (Bool, Expr)
gtcc = ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> GenM' Expr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Bool, Expr)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair ((GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool)
-> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall a b. (a -> b) -> a -> b
$ (GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoCondNeg_Pos) GenM' Expr
garbageExpr
ged :: ReaderT (GarbageOpts, Gen RealWorld) IO (Vector Bool)
ged = do
Vector Bool
v <- Int
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Vector Bool)
forall (m :: * -> *) a.
(Monad m, Unbox a) =>
Int -> m a -> m (Vector a)
VU.replicateM Int
6 ((GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool)
-> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall a b. (a -> b) -> a -> b
$ (GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoEventEdge)
Vector Bool
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Vector Bool)
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (if Vector Bool -> Bool
VU.or Vector Bool
v then Vector Bool
v else Int -> Bool -> Vector Bool
forall a. Unbox a => Int -> a -> Vector a
VU.replicate Int
6 Bool
True)
gtce :: ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
gtce =
Maybe (Vector Bool)
-> SpecTerm -> Maybe (Bool, Expr) -> TimingCheckEvent
TimingCheckEvent (Maybe (Vector Bool)
-> SpecTerm -> Maybe (Bool, Expr) -> TimingCheckEvent)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Vector Bool))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(SpecTerm -> Maybe (Bool, Expr) -> TimingCheckEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Vector Bool)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Vector Bool))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoEvent) ReaderT (GarbageOpts, Gen RealWorld) IO (Vector Bool)
ged
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(SpecTerm -> Maybe (Bool, Expr) -> TimingCheckEvent)
-> GenM' SpecTerm
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Bool, Expr) -> TimingCheckEvent)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' SpecTerm
garbageSpecTerm
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Bool, Expr) -> TimingCheckEvent)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Bool, Expr))
-> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Bool, Expr)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Bool, Expr))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoCondition) ReaderT (GarbageOpts, Gen RealWorld) IO (Bool, Expr)
gtcc
gctce :: ReaderT (GarbageOpts, Gen RealWorld) IO ControlledTimingCheckEvent
gctce =
Vector Bool
-> SpecTerm -> Maybe (Bool, Expr) -> ControlledTimingCheckEvent
ControlledTimingCheckEvent (Vector Bool
-> SpecTerm -> Maybe (Bool, Expr) -> ControlledTimingCheckEvent)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Vector Bool)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(SpecTerm -> Maybe (Bool, Expr) -> ControlledTimingCheckEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (Vector Bool)
ged
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(SpecTerm -> Maybe (Bool, Expr) -> ControlledTimingCheckEvent)
-> GenM' SpecTerm
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Bool, Expr) -> ControlledTimingCheckEvent)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' SpecTerm
garbageSpecTerm
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Bool, Expr) -> ControlledTimingCheckEvent)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Bool, Expr))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ControlledTimingCheckEvent
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Bool, Expr)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Bool, Expr))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoCondition) ReaderT (GarbageOpts, Gen RealWorld) IO (Bool, Expr)
gtcc
gstca :: ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
gstca =
TimingCheckEvent
-> TimingCheckEvent -> Expr -> Maybe Identifier -> STCArgs
STCArgs (TimingCheckEvent
-> TimingCheckEvent -> Expr -> Maybe Identifier -> STCArgs)
-> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(TimingCheckEvent -> Expr -> Maybe Identifier -> STCArgs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
gtce ReaderT
(GarbageOpts, Gen RealWorld)
IO
(TimingCheckEvent -> Expr -> Maybe Identifier -> STCArgs)
-> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> Maybe Identifier -> STCArgs)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO TimingCheckEvent
gtce ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Expr -> Maybe Identifier -> STCArgs)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe Identifier -> STCArgs)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe Identifier -> STCArgs)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCArgs
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Identifier)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) GenM' Identifier
garbageIdent
gstcaa :: ReaderT (GarbageOpts, Gen RealWorld) IO STCAddArgs
gstcaa = Expr
-> Maybe MinTypMax
-> Maybe MinTypMax
-> Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax))
-> STCAddArgs
STCAddArgs (Expr
-> Maybe MinTypMax
-> Maybe MinTypMax
-> Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax))
-> STCAddArgs)
-> GenM' Expr
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe MinTypMax
-> Maybe MinTypMax
-> Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax))
-> STCAddArgs)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Expr
garbageExpr ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe MinTypMax
-> Maybe MinTypMax
-> Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax))
-> STCAddArgs)
-> GenM' (Maybe MinTypMax)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe MinTypMax
-> Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax))
-> STCAddArgs)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (Maybe MinTypMax)
gmmtm ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe MinTypMax
-> Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax))
-> STCAddArgs)
-> GenM' (Maybe MinTypMax)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax)) -> STCAddArgs)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' (Maybe MinTypMax)
gmmtm ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax))
-> Maybe (Identified (Maybe CMinTypMax)) -> STCAddArgs)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)) -> STCAddArgs)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)))
gde ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)) -> STCAddArgs)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)))
-> ReaderT (GarbageOpts, Gen RealWorld) IO STCAddArgs
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)))
gde
gmmtm :: GenM' (Maybe MinTypMax)
gmmtm = (GarbageOpts -> Double)
-> GenM' MinTypMax -> GenM' (Maybe MinTypMax)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) GenM' MinTypMax
garbageMinTypMax
gde :: ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)))
gde = (GarbageOpts -> Double)
-> GenM GarbageOpts (Identified (Maybe CMinTypMax))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)))
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg) (GenM GarbageOpts (Identified (Maybe CMinTypMax))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax))))
-> GenM GarbageOpts (Identified (Maybe CMinTypMax))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Identified (Maybe CMinTypMax)))
forall a b. (a -> b) -> a -> b
$
GenM' (Maybe CMinTypMax)
-> GenM GarbageOpts (Identified (Maybe CMinTypMax))
forall x. GenM' x -> GenM' (Identified x)
garbageIdentified (GenM' (Maybe CMinTypMax)
-> GenM GarbageOpts (Identified (Maybe CMinTypMax)))
-> GenM' (Maybe CMinTypMax)
-> GenM GarbageOpts (Identified (Maybe CMinTypMax))
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> Double)
-> GenM' CMinTypMax -> GenM' (Maybe CMinTypMax)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageSpecifyTimingCheckOpts -> Double) -> GarbageOpts -> Double
forall {c}.
(GarbageSpecifyTimingCheckOpts -> c) -> GarbageOpts -> c
t GarbageSpecifyTimingCheckOpts -> Double
_gstcoDelayedMinTypMax) GenM' CMinTypMax
garbageCMinTypMax
garbageModuleBlock :: Bool -> GenM' ModuleBlock
garbageModuleBlock :: Bool -> GenM' ModuleBlock
garbageModuleBlock Bool
ts = do
Bool
nah <- ((GarbageOpts, Gen RealWorld) -> Bool)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks (((GarbageOpts, Gen RealWorld) -> Bool)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool)
-> ((GarbageOpts, Gen RealWorld) -> Bool)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall a b. (a -> b) -> a -> b
$ (GarbageModuleOpts -> Bool) -> GarbageOpts -> Bool
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Bool
_gmoNonAsciiHeader (GarbageOpts -> Bool)
-> ((GarbageOpts, Gen RealWorld) -> GarbageOpts)
-> (GarbageOpts, Gen RealWorld)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GarbageOpts, Gen RealWorld) -> GarbageOpts
forall a b. (a, b) -> a
fst
[Identified [Identified (Maybe CRangeExpr)]]
header <- (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (Identified [Identified (Maybe CRangeExpr)])
-> GenM GarbageOpts [Identified [Identified (Maybe CRangeExpr)]]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoPorts) (GenM GarbageOpts (Identified [Identified (Maybe CRangeExpr)])
-> GenM GarbageOpts [Identified [Identified (Maybe CRangeExpr)]])
-> GenM GarbageOpts (Identified [Identified (Maybe CRangeExpr)])
-> GenM GarbageOpts [Identified [Identified (Maybe CRangeExpr)]]
forall a b. (a -> b) -> a -> b
$
if Bool
nah
then
GenM' [Identified (Maybe CRangeExpr)]
-> GenM GarbageOpts (Identified [Identified (Maybe CRangeExpr)])
forall x. GenM' x -> GenM' (Identified x)
garbageIdentified (GenM' [Identified (Maybe CRangeExpr)]
-> GenM GarbageOpts (Identified [Identified (Maybe CRangeExpr)]))
-> GenM' [Identified (Maybe CRangeExpr)]
-> GenM GarbageOpts (Identified [Identified (Maybe CRangeExpr)])
forall a b. (a -> b) -> a -> b
$
(GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (Identified (Maybe CRangeExpr))
-> GenM' [Identified (Maybe CRangeExpr)]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoPortLValues) (GenM GarbageOpts (Identified (Maybe CRangeExpr))
-> GenM' [Identified (Maybe CRangeExpr)])
-> GenM GarbageOpts (Identified (Maybe CRangeExpr))
-> GenM' [Identified (Maybe CRangeExpr)]
forall a b. (a -> b) -> a -> b
$
GenM' (Maybe CRangeExpr)
-> GenM GarbageOpts (Identified (Maybe CRangeExpr))
forall x. GenM' x -> GenM' (Identified x)
garbageIdentified (GenM' (Maybe CRangeExpr)
-> GenM GarbageOpts (Identified (Maybe CRangeExpr)))
-> GenM' (Maybe CRangeExpr)
-> GenM GarbageOpts (Identified (Maybe CRangeExpr))
forall a b. (a -> b) -> a -> b
$ (GarbageOpts -> Double)
-> GenM GarbageOpts CRangeExpr -> GenM' (Maybe CRangeExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageModuleOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Double
_gmoPortRange) GenM GarbageOpts CRangeExpr
garbageCRangeExpr
else (\Identifier
i -> Identifier
-> [Identified (Maybe CRangeExpr)]
-> Identified [Identified (Maybe CRangeExpr)]
forall t. Identifier -> t -> Identified t
Identified Identifier
i [Identifier -> Maybe CRangeExpr -> Identified (Maybe CRangeExpr)
forall t. Identifier -> t -> Identified t
Identified Identifier
i Maybe CRangeExpr
forall a. Maybe a
Nothing]) (Identifier -> Identified [Identified (Maybe CRangeExpr)])
-> GenM' Identifier
-> GenM GarbageOpts (Identified [Identified (Maybe CRangeExpr)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent
Attributes
-> Identifier
-> [Identified [Identified (Maybe CRangeExpr)]]
-> [ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock
ModuleBlock (Attributes
-> Identifier
-> [Identified [Identified (Maybe CRangeExpr)]]
-> [ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock)
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> [Identified [Identified (Maybe CRangeExpr)]]
-> [ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Attributes
garbageAttributes
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> [Identified [Identified (Maybe CRangeExpr)]]
-> [ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
([Identified [Identified (Maybe CRangeExpr)]]
-> [ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
([Identified [Identified (Maybe CRangeExpr)]]
-> [ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock)
-> GenM GarbageOpts [Identified [Identified (Maybe CRangeExpr)]]
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
([ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Identified [Identified (Maybe CRangeExpr)]]
-> GenM GarbageOpts [Identified [Identified (Maybe CRangeExpr)]]
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Identified [Identified (Maybe CRangeExpr)]]
header
ReaderT
(GarbageOpts, Gen RealWorld)
IO
([ModuleItem]
-> Maybe (Int, Int)
-> Bool
-> Maybe Bool
-> Maybe NetType
-> ModuleBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleItem]
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Int, Int)
-> Bool -> Maybe Bool -> Maybe NetType -> ModuleBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts ModuleItem
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleItem]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN
((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoItems)
( (GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts ModuleItem] -> GenM GarbageOpts ModuleItem
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbageModuleOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> CategoricalProbability
_gmoItem)
[ Attributed ModGenBlockedItem -> ModuleItem
MIMGI (Attributed ModGenBlockedItem -> ModuleItem)
-> GenM' (Attributed ModGenBlockedItem)
-> GenM GarbageOpts ModuleItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' (Attributed ModGenBlockedItem)
garbageModGenBlockedItem,
AttrIded (Dir, SignRange) -> ModuleItem
MIPort (AttrIded (Dir, SignRange) -> ModuleItem)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (AttrIded (Dir, SignRange))
-> GenM GarbageOpts ModuleItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' (Dir, SignRange)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (AttrIded (Dir, SignRange))
forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded (GenM' Dir -> GenM' SignRange -> GenM' (Dir, SignRange)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair ((GarbageOpts -> CategoricalProbability) -> GenM' Dir
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM' Dir)
-> (GarbageOpts -> CategoricalProbability) -> GenM' Dir
forall a b. (a -> b) -> a -> b
$ (GarbageModuleOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> CategoricalProbability
_gmoPortDir) GenM' SignRange
garbageSR),
AttrIded Parameter -> ModuleItem
MIParameter (AttrIded Parameter -> ModuleItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (AttrIded Parameter)
-> GenM GarbageOpts ModuleItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Parameter
-> ReaderT (GarbageOpts, Gen RealWorld) IO (AttrIded Parameter)
forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded GenM' Parameter
garbageParameter,
[Attributed ModGenBlockedItem] -> ModuleItem
MIGenReg ([Attributed ModGenBlockedItem] -> ModuleItem)
-> GenM' [Attributed ModGenBlockedItem]
-> GenM GarbageOpts ModuleItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM' (Attributed ModGenBlockedItem)
-> GenM' [Attributed ModGenBlockedItem]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN (GarbageGenerateOpts -> NumberProbability
_ggoItems (GarbageGenerateOpts -> NumberProbability)
-> (GarbageOpts -> GarbageGenerateOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageGenerateOpts
_goGenerate) GenM' (Attributed ModGenBlockedItem)
garbageModGenBlockedItem,
[SpecifyBlockedItem] -> ModuleItem
MISpecBlock ([SpecifyBlockedItem] -> ModuleItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [SpecifyBlockedItem]
-> GenM GarbageOpts ModuleItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts SpecifyBlockedItem
-> ReaderT (GarbageOpts, Gen RealWorld) IO [SpecifyBlockedItem]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN (GarbageSpecifyOpts -> NumberProbability
_gsyoItems (GarbageSpecifyOpts -> NumberProbability)
-> (GarbageOpts -> GarbageSpecifyOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageSpecifyOpts
_goSpecify) GenM GarbageOpts SpecifyBlockedItem
garbageSpecifyItem,
Attributes -> Maybe Range2 -> SpecParamDecl -> ModuleItem
MISpecParam (Attributes -> Maybe Range2 -> SpecParamDecl -> ModuleItem)
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Range2 -> SpecParamDecl -> ModuleItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Attributes
garbageAttributes ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Range2 -> SpecParamDecl -> ModuleItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (SpecParamDecl -> ModuleItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
garbageSPRange ReaderT
(GarbageOpts, Gen RealWorld) IO (SpecParamDecl -> ModuleItem)
-> GenM' SpecParamDecl -> GenM GarbageOpts ModuleItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' SpecParamDecl
garbageSpecParamAssign,
Attributes -> Maybe Range2 -> SpecParamDecl -> ModuleItem
MISpecParam (Attributes -> Maybe Range2 -> SpecParamDecl -> ModuleItem)
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Range2 -> SpecParamDecl -> ModuleItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Attributes
garbageAttributes ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Range2 -> SpecParamDecl -> ModuleItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (SpecParamDecl -> ModuleItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
garbageSPRange ReaderT
(GarbageOpts, Gen RealWorld) IO (SpecParamDecl -> ModuleItem)
-> GenM' SpecParamDecl -> GenM GarbageOpts ModuleItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' SpecParamDecl
garbageNoPathPulse,
Attributes -> Maybe Range2 -> SpecParamDecl -> ModuleItem
MISpecParam (Attributes -> Maybe Range2 -> SpecParamDecl -> ModuleItem)
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Range2 -> SpecParamDecl -> ModuleItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Attributes
garbageAttributes ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Range2 -> SpecParamDecl -> ModuleItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (SpecParamDecl -> ModuleItem)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Range2)
garbageSPRange ReaderT
(GarbageOpts, Gen RealWorld) IO (SpecParamDecl -> ModuleItem)
-> GenM' SpecParamDecl -> GenM GarbageOpts ModuleItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' SpecParamDecl
garbagePathPulse
]
)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe (Int, Int)
-> Bool -> Maybe Bool -> Maybe NetType -> ModuleBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Int, Int))
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Bool -> Maybe Bool -> Maybe NetType -> ModuleBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (if Bool
ts then (Int, Int) -> Maybe (Int, Int)
forall a. a -> Maybe a
Just ((Int, Int) -> Maybe (Int, Int))
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Int, Int)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Int, Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Int
-> GenM' Int -> ReaderT (GarbageOpts, Gen RealWorld) IO (Int, Int)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f (a, b)
mkpair GenM' Int
gts GenM' Int
gts else Maybe (Int, Int)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe (Int, Int))
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (Int, Int)
forall a. Maybe a
Nothing)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Bool -> Maybe Bool -> Maybe NetType -> ModuleBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Bool -> Maybe NetType -> ModuleBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageModuleOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Double
_gmoCell)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Maybe Bool -> Maybe NetType -> ModuleBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe NetType -> ModuleBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe Bool)
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p (Maybe a)
sampleMaybeEnum ((GarbageModuleOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> CategoricalProbability
_gmoUnconnectedDrive)
ReaderT
(GarbageOpts, Gen RealWorld) IO (Maybe NetType -> ModuleBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe NetType)
-> GenM' ModuleBlock
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe NetType)
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p (Maybe a)
sampleMaybeEnum ((GarbageModuleOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> CategoricalProbability
_gmoDefaultNetType)
where
m :: (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> c
x = GarbageModuleOpts -> c
x (GarbageModuleOpts -> c)
-> (GarbageOpts -> GarbageModuleOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageModuleOpts
_goModule
gts :: GenM' Int
gts = (GarbageOpts -> CategoricalProbability) -> Int -> Int -> GenM' Int
forall p. (p -> CategoricalProbability) -> Int -> Int -> GenM p Int
sampleSegment ((GarbageModuleOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> CategoricalProbability
_gmoTimeMagnitude) (-Int
15) Int
2
garbagePrimitiveBlock :: GenM' PrimitiveBlock
garbagePrimitiveBlock :: GenM' PrimitiveBlock
garbagePrimitiveBlock =
Attributes
-> Identifier
-> Identifier
-> NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort)
-> PrimTable
-> PrimitiveBlock
PrimitiveBlock (Attributes
-> Identifier
-> Identifier
-> NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort)
-> PrimTable
-> PrimitiveBlock)
-> GenM' Attributes
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> Identifier
-> NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort)
-> PrimTable
-> PrimitiveBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Attributes
garbageAttributes
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> Identifier
-> NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort)
-> PrimTable
-> PrimitiveBlock)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort)
-> PrimTable
-> PrimitiveBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(Identifier
-> NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort)
-> PrimTable
-> PrimitiveBlock)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort) -> PrimTable -> PrimitiveBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty Identifier
-> NonEmpty (AttrIded PrimPort) -> PrimTable -> PrimitiveBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Identifier)
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty (AttrIded PrimPort) -> PrimTable -> PrimitiveBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Identifier)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbagePrimitiveOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> NumberProbability
_gpoPorts) GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
(NonEmpty (AttrIded PrimPort) -> PrimTable -> PrimitiveBlock)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty (AttrIded PrimPort))
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (PrimTable -> PrimitiveBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts (AttrIded PrimPort)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty (AttrIded PrimPort))
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbagePrimitiveOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> NumberProbability
_gpoPorts) (GenM GarbageOpts PrimPort -> GenM GarbageOpts (AttrIded PrimPort)
forall x. GenM' x -> GenM' (AttrIded x)
garbageAttrIded (GenM GarbageOpts PrimPort -> GenM GarbageOpts (AttrIded PrimPort))
-> GenM GarbageOpts PrimPort
-> GenM GarbageOpts (AttrIded PrimPort)
forall a b. (a -> b) -> a -> b
$
(GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts PrimPort] -> GenM GarbageOpts PrimPort
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch ((GarbagePrimitiveOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> CategoricalProbability
_gpoPortType)
[ PrimPort -> GenM GarbageOpts PrimPort
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PrimPort
PPInput,
PrimPort -> GenM GarbageOpts PrimPort
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PrimPort
PPOutput,
PrimPort -> GenM GarbageOpts PrimPort
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PrimPort
PPReg,
Maybe CExpr -> PrimPort
PPOutReg (Maybe CExpr -> PrimPort)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
-> GenM GarbageOpts PrimPort
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> GenM GarbageOpts CExpr
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe CExpr)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbagePrimitiveOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> Double
_gpoRegInit) GenM GarbageOpts CExpr
garbageCExpr
])
ReaderT
(GarbageOpts, Gen RealWorld) IO (PrimTable -> PrimitiveBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO PrimTable
-> GenM' PrimitiveBlock
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO PrimTable
-> ReaderT (GarbageOpts, Gen RealWorld) IO PrimTable
-> ReaderT (GarbageOpts, Gen RealWorld) IO PrimTable
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbagePrimitiveOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> Double
_gpoSeq_Comb)
( Maybe ZOX -> NonEmpty SeqRow -> PrimTable
SeqTable
(Maybe ZOX -> NonEmpty SeqRow -> PrimTable)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ZOX)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty SeqRow -> PrimTable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> CategoricalProbability)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ZOX)
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p (Maybe a)
sampleMaybeEnum ((GarbagePrimitiveOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> CategoricalProbability
_gpoCombInit)
ReaderT
(GarbageOpts, Gen RealWorld) IO (NonEmpty SeqRow -> PrimTable)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SeqRow)
-> ReaderT (GarbageOpts, Gen RealWorld) IO PrimTable
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts SeqRow
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SeqRow)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbagePrimitiveOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> NumberProbability
_gpoTableRows) GenM GarbageOpts SeqRow
gseqrow
)
(NonEmpty CombRow -> PrimTable
CombTable (NonEmpty CombRow -> PrimTable)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty CombRow)
-> ReaderT (GarbageOpts, Gen RealWorld) IO PrimTable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts CombRow
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty CombRow)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbagePrimitiveOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> NumberProbability
_gpoTableRows) (NonEmpty SigLevel -> ZOX -> CombRow
CombRow (NonEmpty SigLevel -> ZOX -> CombRow)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SigLevel)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (ZOX -> CombRow)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SigLevel)
gnein ReaderT (GarbageOpts, Gen RealWorld) IO (ZOX -> CombRow)
-> GenM GarbageOpts ZOX -> GenM GarbageOpts CombRow
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts ZOX
goutlv))
where
p :: (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> c
x = GarbagePrimitiveOpts -> c
x (GarbagePrimitiveOpts -> c)
-> (GarbageOpts -> GarbagePrimitiveOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbagePrimitiveOpts
_goPrimitive
ginlv :: GenM GarbageOpts SigLevel
ginlv = (GarbageOpts -> CategoricalProbability)
-> GenM GarbageOpts SigLevel
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability)
-> GenM GarbageOpts SigLevel)
-> (GarbageOpts -> CategoricalProbability)
-> GenM GarbageOpts SigLevel
forall a b. (a -> b) -> a -> b
$ (GarbagePrimitiveOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> CategoricalProbability
_gpoInLevel
goutlv :: GenM GarbageOpts ZOX
goutlv = (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX
forall a p.
(Bounded a, Enum a) =>
(p -> CategoricalProbability) -> GenM p a
sampleEnum ((GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX)
-> (GarbageOpts -> CategoricalProbability) -> GenM GarbageOpts ZOX
forall a b. (a -> b) -> a -> b
$ (GarbagePrimitiveOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> CategoricalProbability
_gpoOutLevel
gnein :: ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SigLevel)
gnein = (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts SigLevel
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SigLevel)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE ((GarbagePrimitiveOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> NumberProbability
_gpoPorts) GenM GarbageOpts SigLevel
ginlv
glin :: GenM GarbageOpts [SigLevel]
glin = (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts SigLevel -> GenM GarbageOpts [SigLevel]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbagePrimitiveOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> NumberProbability
_gpoPorts) GenM GarbageOpts SigLevel
ginlv
gedgeseq :: ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
gedgeseq =
[SigLevel] -> Edge -> [SigLevel] -> SeqIn
SISeq ([SigLevel] -> Edge -> [SigLevel] -> SeqIn)
-> GenM GarbageOpts [SigLevel]
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Edge -> [SigLevel] -> SeqIn)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts [SigLevel]
glin
ReaderT
(GarbageOpts, Gen RealWorld) IO (Edge -> [SigLevel] -> SeqIn)
-> GenM GarbageOpts Edge
-> ReaderT (GarbageOpts, Gen RealWorld) IO ([SigLevel] -> SeqIn)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> CategoricalProbability)
-> [GenM GarbageOpts Edge] -> GenM GarbageOpts Edge
forall p a. (p -> CategoricalProbability) -> [GenM p a] -> GenM p a
sampleBranch
((GarbagePrimitiveOpts -> CategoricalProbability)
-> GarbageOpts -> CategoricalProbability
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> CategoricalProbability
_gpoEdgeSimplePosNeg)
[ SigLevel -> SigLevel -> Edge
EdgeDesc (SigLevel -> SigLevel -> Edge)
-> GenM GarbageOpts SigLevel
-> ReaderT (GarbageOpts, Gen RealWorld) IO (SigLevel -> Edge)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts SigLevel
ginlv ReaderT (GarbageOpts, Gen RealWorld) IO (SigLevel -> Edge)
-> GenM GarbageOpts SigLevel -> GenM GarbageOpts Edge
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts SigLevel
ginlv,
Edge -> GenM GarbageOpts Edge
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Edge -> GenM GarbageOpts Edge) -> Edge -> GenM GarbageOpts Edge
forall a b. (a -> b) -> a -> b
$ Bool -> Edge
EdgePos_neg Bool
True,
Edge -> GenM GarbageOpts Edge
forall a. a -> ReaderT (GarbageOpts, Gen RealWorld) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Edge -> GenM GarbageOpts Edge) -> Edge -> GenM GarbageOpts Edge
forall a b. (a -> b) -> a -> b
$ Bool -> Edge
EdgePos_neg Bool
False
]
ReaderT (GarbageOpts, Gen RealWorld) IO ([SigLevel] -> SeqIn)
-> GenM GarbageOpts [SigLevel]
-> ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts [SigLevel]
glin
gseqrow :: GenM GarbageOpts SeqRow
gseqrow =
SeqIn -> SigLevel -> Maybe ZOX -> SeqRow
SeqRow (SeqIn -> SigLevel -> Maybe ZOX -> SeqRow)
-> ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (SigLevel -> Maybe ZOX -> SeqRow)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
-> ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
-> ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice ((GarbagePrimitiveOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> Double
_gpoEdgeSensitive) (NonEmpty SigLevel -> SeqIn
SIComb (NonEmpty SigLevel -> SeqIn)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SigLevel)
-> ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty SigLevel)
gnein) ReaderT (GarbageOpts, Gen RealWorld) IO SeqIn
gedgeseq
ReaderT
(GarbageOpts, Gen RealWorld) IO (SigLevel -> Maybe ZOX -> SeqRow)
-> GenM GarbageOpts SigLevel
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ZOX -> SeqRow)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM GarbageOpts SigLevel
ginlv
ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ZOX -> SeqRow)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ZOX)
-> GenM GarbageOpts SeqRow
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> GenM GarbageOpts ZOX
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ZOX)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbagePrimitiveOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbagePrimitiveOpts -> c) -> GarbageOpts -> c
p GarbagePrimitiveOpts -> Double
_gpoOutputNoChange) GenM GarbageOpts ZOX
goutlv
garbageVerilog2005 :: GenM' Verilog2005
garbageVerilog2005 :: GenM' Verilog2005
garbageVerilog2005 =
[ModuleBlock] -> [PrimitiveBlock] -> [ConfigBlock] -> Verilog2005
Verilog2005
([ModuleBlock] -> [PrimitiveBlock] -> [ConfigBlock] -> Verilog2005)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleBlock]
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
([PrimitiveBlock] -> [ConfigBlock] -> Verilog2005)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageModuleOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> Double
_gmoTimeScale) ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> (Bool -> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleBlock])
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleBlock]
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO a
-> (a -> ReaderT (GarbageOpts, Gen RealWorld) IO b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (GarbageOpts -> NumberProbability)
-> GenM' ModuleBlock
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleBlock]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageModuleOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> NumberProbability
_gmoBlocks) (GenM' ModuleBlock
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleBlock])
-> (Bool -> GenM' ModuleBlock)
-> Bool
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ModuleBlock]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> GenM' ModuleBlock
garbageModuleBlock)
ReaderT
(GarbageOpts, Gen RealWorld)
IO
([PrimitiveBlock] -> [ConfigBlock] -> Verilog2005)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [PrimitiveBlock]
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ([ConfigBlock] -> Verilog2005)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM' PrimitiveBlock
-> ReaderT (GarbageOpts, Gen RealWorld) IO [PrimitiveBlock]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN (GarbagePrimitiveOpts -> NumberProbability
_gpoBlocks (GarbagePrimitiveOpts -> NumberProbability)
-> (GarbageOpts -> GarbagePrimitiveOpts)
-> GarbageOpts
-> NumberProbability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbagePrimitiveOpts
_goPrimitive) GenM' PrimitiveBlock
garbagePrimitiveBlock
ReaderT
(GarbageOpts, Gen RealWorld) IO ([ConfigBlock] -> Verilog2005)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ConfigBlock]
-> GenM' Verilog2005
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts ConfigBlock
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ConfigBlock]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN
((GarbageConfigOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> NumberProbability
_gcoBlocks)
( Identifier
-> [Dot1Ident] -> [ConfigItem] -> [ByteString] -> ConfigBlock
ConfigBlock (Identifier
-> [Dot1Ident] -> [ConfigItem] -> [ByteString] -> ConfigBlock)
-> GenM' Identifier
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
([Dot1Ident] -> [ConfigItem] -> [ByteString] -> ConfigBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM' Identifier
garbageIdent
ReaderT
(GarbageOpts, Gen RealWorld)
IO
([Dot1Ident] -> [ConfigItem] -> [ByteString] -> ConfigBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Dot1Ident]
-> ReaderT
(GarbageOpts, Gen RealWorld)
IO
([ConfigItem] -> [ByteString] -> ConfigBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts Dot1Ident
-> ReaderT (GarbageOpts, Gen RealWorld) IO [Dot1Ident]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageConfigOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> NumberProbability
_gcoDesigns) GenM GarbageOpts Dot1Ident
gdot1
ReaderT
(GarbageOpts, Gen RealWorld)
IO
([ConfigItem] -> [ByteString] -> ConfigBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ConfigItem]
-> ReaderT
(GarbageOpts, Gen RealWorld) IO ([ByteString] -> ConfigBlock)
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> GenM GarbageOpts ConfigItem
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ConfigItem]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN
((GarbageConfigOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> NumberProbability
_gcoItems)
( Cell_inst -> LLU -> ConfigItem
ConfigItem
(Cell_inst -> LLU -> ConfigItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Cell_inst
-> ReaderT (GarbageOpts, Gen RealWorld) IO (LLU -> ConfigItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Cell_inst
-> ReaderT (GarbageOpts, Gen RealWorld) IO Cell_inst
-> ReaderT (GarbageOpts, Gen RealWorld) IO Cell_inst
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbageConfigOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> Double
_gcoCell_Inst)
(Dot1Ident -> Cell_inst
CICell (Dot1Ident -> Cell_inst)
-> GenM GarbageOpts Dot1Ident
-> ReaderT (GarbageOpts, Gen RealWorld) IO Cell_inst
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts Dot1Ident
gdot1)
(NonEmpty Identifier -> Cell_inst
CIInst (NonEmpty Identifier -> Cell_inst)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Identifier)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Cell_inst
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> NumberProbability)
-> GenM' Identifier
-> ReaderT (GarbageOpts, Gen RealWorld) IO (NonEmpty Identifier)
forall p b.
(p -> NumberProbability) -> GenM p b -> GenM p (NonEmpty b)
sampleNE GarbageOpts -> NumberProbability
_goPathDepth GenM' Identifier
garbageIdent)
ReaderT (GarbageOpts, Gen RealWorld) IO (LLU -> ConfigItem)
-> ReaderT (GarbageOpts, Gen RealWorld) IO LLU
-> GenM GarbageOpts ConfigItem
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO LLU
-> ReaderT (GarbageOpts, Gen RealWorld) IO LLU
-> ReaderT (GarbageOpts, Gen RealWorld) IO LLU
forall p a. (p -> Double) -> GenM p a -> GenM p a -> GenM p a
choice
((GarbageConfigOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> Double
_gcoLiblist_Use)
([ByteString] -> LLU
LLULiblist ([ByteString] -> LLU)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ByteString]
-> ReaderT (GarbageOpts, Gen RealWorld) IO LLU
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReaderT (GarbageOpts, Gen RealWorld) IO [ByteString]
glibs)
(Dot1Ident -> Bool -> LLU
LLUUse (Dot1Ident -> Bool -> LLU)
-> GenM GarbageOpts Dot1Ident
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Bool -> LLU)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenM GarbageOpts Dot1Ident
gdot1 ReaderT (GarbageOpts, Gen RealWorld) IO (Bool -> LLU)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
-> ReaderT (GarbageOpts, Gen RealWorld) IO LLU
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double)
-> ReaderT (GarbageOpts, Gen RealWorld) IO Bool
forall p. (p -> Double) -> GenM p Bool
sampleBernoulli ((GarbageConfigOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> Double
_gcoConfig))
)
ReaderT
(GarbageOpts, Gen RealWorld) IO ([ByteString] -> ConfigBlock)
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ByteString]
-> GenM GarbageOpts ConfigBlock
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReaderT (GarbageOpts, Gen RealWorld) IO [ByteString]
glibs
)
where
m :: (GarbageModuleOpts -> c) -> GarbageOpts -> c
m GarbageModuleOpts -> c
x = GarbageModuleOpts -> c
x (GarbageModuleOpts -> c)
-> (GarbageOpts -> GarbageModuleOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageModuleOpts
_goModule
c :: (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> c
x = GarbageConfigOpts -> c
x (GarbageConfigOpts -> c)
-> (GarbageOpts -> GarbageConfigOpts) -> GarbageOpts -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GarbageOpts -> GarbageConfigOpts
_goConfig
glibs :: ReaderT (GarbageOpts, Gen RealWorld) IO [ByteString]
glibs = (GarbageOpts -> NumberProbability)
-> GenM' ByteString
-> ReaderT (GarbageOpts, Gen RealWorld) IO [ByteString]
forall p b. (p -> NumberProbability) -> GenM p b -> GenM p [b]
sampleN ((GarbageConfigOpts -> NumberProbability)
-> GarbageOpts -> NumberProbability
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> NumberProbability
_gcoLibraries) GenM' ByteString
garbageBS
gdot1 :: GenM GarbageOpts Dot1Ident
gdot1 = Maybe ByteString -> Identifier -> Dot1Ident
Dot1Ident (Maybe ByteString -> Identifier -> Dot1Ident)
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ByteString)
-> ReaderT
(GarbageOpts, Gen RealWorld) IO (Identifier -> Dot1Ident)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageOpts -> Double)
-> GenM' ByteString
-> ReaderT (GarbageOpts, Gen RealWorld) IO (Maybe ByteString)
forall p a. (p -> Double) -> GenM p a -> GenM p (Maybe a)
sampleMaybe ((GarbageConfigOpts -> Double) -> GarbageOpts -> Double
forall {c}. (GarbageConfigOpts -> c) -> GarbageOpts -> c
c GarbageConfigOpts -> Double
_gcoLibraryScope) GenM' ByteString
garbageBS ReaderT (GarbageOpts, Gen RealWorld) IO (Identifier -> Dot1Ident)
-> GenM' Identifier -> GenM GarbageOpts Dot1Ident
forall a b.
ReaderT (GarbageOpts, Gen RealWorld) IO (a -> b)
-> ReaderT (GarbageOpts, Gen RealWorld) IO a
-> ReaderT (GarbageOpts, Gen RealWorld) IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GenM' Identifier
garbageIdent
runGarbageGeneration :: Config -> IO Verilog2005
runGarbageGeneration :: Config -> IO Verilog2005
runGarbageGeneration Config
c = do
let conf :: GarbageOpts
conf = Config -> GarbageOpts
_configGarbageGenerator Config
c
Gen RealWorld
gen <- IO (Gen RealWorld)
-> (Vector Word32 -> IO (Gen RealWorld))
-> Maybe (Vector Word32)
-> IO (Gen RealWorld)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO (Gen RealWorld)
IO GenIO
createSystemRandom Vector Word32 -> IO (Gen RealWorld)
Vector Word32 -> IO GenIO
forall (m :: * -> *) (v :: * -> *).
(PrimMonad m, Vector v Word32) =>
v Word32 -> m (Gen (PrimState m))
initialize (Maybe (Vector Word32) -> IO (Gen RealWorld))
-> Maybe (Vector Word32) -> IO (Gen RealWorld)
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> Maybe (Vector Word32)
_goSeed GarbageOpts
conf
GenM' Verilog2005 -> (GarbageOpts, Gen RealWorld) -> IO Verilog2005
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT GenM' Verilog2005
garbageVerilog2005 (GarbageOpts
conf, Gen RealWorld
gen)