{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TemplateHaskell #-}
module Verismith.Config
(
Config (..),
defaultConfig,
Probability (..),
ProbExpr (..),
ProbModItem (..),
ProbStatement (..),
ProbMod (..),
ConfEMI (..),
ConfProperty (..),
NumberProbability (..),
CategoricalProbability (..),
uniformCP,
GarbageOpts (..),
GarbageConfigOpts (..),
GarbagePrimitiveOpts (..),
GarbageModuleOpts (..),
GarbageSpecifyOpts (..),
GarbageSpecifyPathOpts (..),
GarbageSpecifyTimingCheckOpts (..),
GarbageGenerateOpts (..),
GarbageTypeOpts (..),
GarbageAttenuationOpts (..),
GarbageStatementOpts (..),
GarbageExprOpts (..),
GarbageIdentifierOpts (..),
defGarbageOpts,
SimDescription (..),
SynthDescription (..),
fromXST,
fromYosys,
fromVivado,
fromQuartus,
fromQuartusLight,
configEMI,
configProbability,
configGarbageGenerator,
configProperty,
configSimulators,
configSynthesisers,
confEMIGenerateProb,
confEMINoGenerateProb,
probModItem,
probMod,
probModDropOutput,
probModKeepOutput,
probStmnt,
probExpr,
probExprNum,
probExprId,
probExprRangeSelect,
probExprUnOp,
probExprBinOp,
probExprCond,
probExprConcat,
probExprStr,
probExprSigned,
probExprUnsigned,
probModItemAssign,
probModItemSeqAlways,
probModItemCombAlways,
probModItemInst,
probStmntBlock,
probStmntNonBlock,
probStmntCond,
probStmntFor,
propSampleSize,
propSampleMethod,
propSize,
propSeed,
propStmntDepth,
propModDepth,
propMaxModules,
propCombine,
propDeterminism,
propNonDeterminism,
propDefaultYosys,
goSeed,
gaoCurrent,
goGenerate,
goStatement,
goExpr,
ggoAttenuation,
geoAttenuation,
gstoAttenuation,
parseConfigFile,
parseConfig,
parseConfigFileRelaxed,
parseConfigRelaxed,
encodeConfig,
encodeConfigFile,
versionInfo,
)
where
import Control.Applicative (Alternative, liftA2, liftA3, (<|>))
import Control.Lens hiding ((.=))
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe (fromMaybe)
import Data.Text (Text, pack, unpack)
import qualified Data.Text.IO as T
import qualified Data.Vector.Unboxed as VU
import Data.Version (showVersion)
import Data.Word (Word32)
import Development.GitRev
import Hedgehog.Internal.Seed (Seed)
import Paths_verismith (version)
import Shelly (toTextIgnore)
import Toml (TomlCodec, (.=))
import qualified Toml
import Verismith.Tool.Quartus
import Verismith.Tool.QuartusLight
import Verismith.Tool.Vivado
import Verismith.Tool.XST
import Verismith.Tool.Yosys
import Verismith.Utils (uncurry3)
data ProbExpr = ProbExpr
{
ProbExpr -> Int
_probExprNum :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprId :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprRangeSelect :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprUnOp :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprBinOp :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprCond :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprConcat :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprStr :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprSigned :: {-# UNPACK #-} !Int,
ProbExpr -> Int
_probExprUnsigned :: {-# UNPACK #-} !Int
}
deriving (ProbExpr -> ProbExpr -> Bool
(ProbExpr -> ProbExpr -> Bool)
-> (ProbExpr -> ProbExpr -> Bool) -> Eq ProbExpr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProbExpr -> ProbExpr -> Bool
== :: ProbExpr -> ProbExpr -> Bool
$c/= :: ProbExpr -> ProbExpr -> Bool
/= :: ProbExpr -> ProbExpr -> Bool
Eq, Int -> ProbExpr -> ShowS
[ProbExpr] -> ShowS
ProbExpr -> String
(Int -> ProbExpr -> ShowS)
-> (ProbExpr -> String) -> ([ProbExpr] -> ShowS) -> Show ProbExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProbExpr -> ShowS
showsPrec :: Int -> ProbExpr -> ShowS
$cshow :: ProbExpr -> String
show :: ProbExpr -> String
$cshowList :: [ProbExpr] -> ShowS
showList :: [ProbExpr] -> ShowS
Show)
data ProbModItem = ProbModItem
{
ProbModItem -> Int
_probModItemAssign :: {-# UNPACK #-} !Int,
ProbModItem -> Int
_probModItemSeqAlways :: {-# UNPACK #-} !Int,
ProbModItem -> Int
_probModItemCombAlways :: {-# UNPACK #-} !Int,
ProbModItem -> Int
_probModItemInst :: {-# UNPACK #-} !Int
}
deriving (ProbModItem -> ProbModItem -> Bool
(ProbModItem -> ProbModItem -> Bool)
-> (ProbModItem -> ProbModItem -> Bool) -> Eq ProbModItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProbModItem -> ProbModItem -> Bool
== :: ProbModItem -> ProbModItem -> Bool
$c/= :: ProbModItem -> ProbModItem -> Bool
/= :: ProbModItem -> ProbModItem -> Bool
Eq, Int -> ProbModItem -> ShowS
[ProbModItem] -> ShowS
ProbModItem -> String
(Int -> ProbModItem -> ShowS)
-> (ProbModItem -> String)
-> ([ProbModItem] -> ShowS)
-> Show ProbModItem
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProbModItem -> ShowS
showsPrec :: Int -> ProbModItem -> ShowS
$cshow :: ProbModItem -> String
show :: ProbModItem -> String
$cshowList :: [ProbModItem] -> ShowS
showList :: [ProbModItem] -> ShowS
Show)
data ProbStatement = ProbStatement
{
ProbStatement -> Int
_probStmntBlock :: {-# UNPACK #-} !Int,
ProbStatement -> Int
_probStmntNonBlock :: {-# UNPACK #-} !Int,
ProbStatement -> Int
_probStmntCond :: {-# UNPACK #-} !Int,
ProbStatement -> Int
_probStmntFor :: {-# UNPACK #-} !Int
}
deriving (ProbStatement -> ProbStatement -> Bool
(ProbStatement -> ProbStatement -> Bool)
-> (ProbStatement -> ProbStatement -> Bool) -> Eq ProbStatement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProbStatement -> ProbStatement -> Bool
== :: ProbStatement -> ProbStatement -> Bool
$c/= :: ProbStatement -> ProbStatement -> Bool
/= :: ProbStatement -> ProbStatement -> Bool
Eq, Int -> ProbStatement -> ShowS
[ProbStatement] -> ShowS
ProbStatement -> String
(Int -> ProbStatement -> ShowS)
-> (ProbStatement -> String)
-> ([ProbStatement] -> ShowS)
-> Show ProbStatement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProbStatement -> ShowS
showsPrec :: Int -> ProbStatement -> ShowS
$cshow :: ProbStatement -> String
show :: ProbStatement -> String
$cshowList :: [ProbStatement] -> ShowS
showList :: [ProbStatement] -> ShowS
Show)
data ProbMod = ProbMod
{
ProbMod -> Int
_probModDropOutput :: {-# UNPACK #-} !Int,
ProbMod -> Int
_probModKeepOutput :: {-# UNPACK #-} !Int
}
deriving (ProbMod -> ProbMod -> Bool
(ProbMod -> ProbMod -> Bool)
-> (ProbMod -> ProbMod -> Bool) -> Eq ProbMod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProbMod -> ProbMod -> Bool
== :: ProbMod -> ProbMod -> Bool
$c/= :: ProbMod -> ProbMod -> Bool
/= :: ProbMod -> ProbMod -> Bool
Eq, Int -> ProbMod -> ShowS
[ProbMod] -> ShowS
ProbMod -> String
(Int -> ProbMod -> ShowS)
-> (ProbMod -> String) -> ([ProbMod] -> ShowS) -> Show ProbMod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProbMod -> ShowS
showsPrec :: Int -> ProbMod -> ShowS
$cshow :: ProbMod -> String
show :: ProbMod -> String
$cshowList :: [ProbMod] -> ShowS
showList :: [ProbMod] -> ShowS
Show)
data Probability = Probability
{
Probability -> ProbModItem
_probModItem :: {-# UNPACK #-} !ProbModItem,
Probability -> ProbStatement
_probStmnt :: {-# UNPACK #-} !ProbStatement,
Probability -> ProbExpr
_probExpr :: {-# UNPACK #-} !ProbExpr,
Probability -> ProbMod
_probMod :: {-# UNPACK #-} !ProbMod
}
deriving (Probability -> Probability -> Bool
(Probability -> Probability -> Bool)
-> (Probability -> Probability -> Bool) -> Eq Probability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Probability -> Probability -> Bool
== :: Probability -> Probability -> Bool
$c/= :: Probability -> Probability -> Bool
/= :: Probability -> Probability -> Bool
Eq, Int -> Probability -> ShowS
[Probability] -> ShowS
Probability -> String
(Int -> Probability -> ShowS)
-> (Probability -> String)
-> ([Probability] -> ShowS)
-> Show Probability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Probability -> ShowS
showsPrec :: Int -> Probability -> ShowS
$cshow :: Probability -> String
show :: Probability -> String
$cshowList :: [Probability] -> ShowS
showList :: [Probability] -> ShowS
Show)
data ConfEMI = ConfEMI
{
ConfEMI -> Int
_confEMIGenerateProb :: {-# UNPACK #-} !Int,
ConfEMI -> Int
_confEMINoGenerateProb :: {-# UNPACK #-} !Int
}
deriving (ConfEMI -> ConfEMI -> Bool
(ConfEMI -> ConfEMI -> Bool)
-> (ConfEMI -> ConfEMI -> Bool) -> Eq ConfEMI
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfEMI -> ConfEMI -> Bool
== :: ConfEMI -> ConfEMI -> Bool
$c/= :: ConfEMI -> ConfEMI -> Bool
/= :: ConfEMI -> ConfEMI -> Bool
Eq, Int -> ConfEMI -> ShowS
[ConfEMI] -> ShowS
ConfEMI -> String
(Int -> ConfEMI -> ShowS)
-> (ConfEMI -> String) -> ([ConfEMI] -> ShowS) -> Show ConfEMI
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfEMI -> ShowS
showsPrec :: Int -> ConfEMI -> ShowS
$cshow :: ConfEMI -> String
show :: ConfEMI -> String
$cshowList :: [ConfEMI] -> ShowS
showList :: [ConfEMI] -> ShowS
Show)
data ConfProperty = ConfProperty
{
ConfProperty -> Int
_propSize :: {-# UNPACK #-} !Int,
ConfProperty -> Maybe Seed
_propSeed :: !(Maybe Seed),
ConfProperty -> Int
_propStmntDepth :: {-# UNPACK #-} !Int,
ConfProperty -> Int
_propModDepth :: {-# UNPACK #-} !Int,
ConfProperty -> Int
_propMaxModules :: {-# UNPACK #-} !Int,
ConfProperty -> Text
_propSampleMethod :: !Text,
ConfProperty -> Int
_propSampleSize :: {-# UNPACK #-} !Int,
ConfProperty -> Bool
_propCombine :: !Bool,
ConfProperty -> Int
_propNonDeterminism :: {-# UNPACK #-} !Int,
ConfProperty -> Int
_propDeterminism :: {-# UNPACK #-} !Int,
ConfProperty -> Maybe Text
_propDefaultYosys :: !(Maybe Text)
}
deriving (ConfProperty -> ConfProperty -> Bool
(ConfProperty -> ConfProperty -> Bool)
-> (ConfProperty -> ConfProperty -> Bool) -> Eq ConfProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConfProperty -> ConfProperty -> Bool
== :: ConfProperty -> ConfProperty -> Bool
$c/= :: ConfProperty -> ConfProperty -> Bool
/= :: ConfProperty -> ConfProperty -> Bool
Eq, Int -> ConfProperty -> ShowS
[ConfProperty] -> ShowS
ConfProperty -> String
(Int -> ConfProperty -> ShowS)
-> (ConfProperty -> String)
-> ([ConfProperty] -> ShowS)
-> Show ConfProperty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfProperty -> ShowS
showsPrec :: Int -> ConfProperty -> ShowS
$cshow :: ConfProperty -> String
show :: ConfProperty -> String
$cshowList :: [ConfProperty] -> ShowS
showList :: [ConfProperty] -> ShowS
Show)
data NumberProbability
= NPUniform
{ NumberProbability -> Int
_NPULow :: !Int,
NumberProbability -> Int
_NPUHigh :: !Int
}
| NPBinomial
{ NumberProbability -> Int
_NPBOffset :: !Int,
NumberProbability -> Int
_NPBTrials :: !Int,
NumberProbability -> Double
_NPBSuccess :: !Double
}
| NPNegativeBinomial
{ NumberProbability -> Int
_NPNBOffset :: !Int,
NumberProbability -> Double
_NPNBFailRate :: !Double,
NumberProbability -> Int
_NPNBFailure :: !Int
}
| NPPoisson
{ NumberProbability -> Int
_NPPOffset :: !Int,
NumberProbability -> Double
_NPPParam :: !Double
}
| NPDiscrete !(NonEmpty (Double, Int))
| NPLinearComb !(NonEmpty (Double, NumberProbability))
deriving (NumberProbability -> NumberProbability -> Bool
(NumberProbability -> NumberProbability -> Bool)
-> (NumberProbability -> NumberProbability -> Bool)
-> Eq NumberProbability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NumberProbability -> NumberProbability -> Bool
== :: NumberProbability -> NumberProbability -> Bool
$c/= :: NumberProbability -> NumberProbability -> Bool
/= :: NumberProbability -> NumberProbability -> Bool
Eq, Int -> NumberProbability -> ShowS
[NumberProbability] -> ShowS
NumberProbability -> String
(Int -> NumberProbability -> ShowS)
-> (NumberProbability -> String)
-> ([NumberProbability] -> ShowS)
-> Show NumberProbability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NumberProbability -> ShowS
showsPrec :: Int -> NumberProbability -> ShowS
$cshow :: NumberProbability -> String
show :: NumberProbability -> String
$cshowList :: [NumberProbability] -> ShowS
showList :: [NumberProbability] -> ShowS
Show)
data CategoricalProbability
= CPDiscrete !(NonEmpty Double)
| CPBiasedUniform
{ CategoricalProbability -> [(Double, Int)]
_CPBUBiases :: ![(Double, Int)],
CategoricalProbability -> Double
_CPBUUniformWeight :: Double
}
deriving (CategoricalProbability -> CategoricalProbability -> Bool
(CategoricalProbability -> CategoricalProbability -> Bool)
-> (CategoricalProbability -> CategoricalProbability -> Bool)
-> Eq CategoricalProbability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CategoricalProbability -> CategoricalProbability -> Bool
== :: CategoricalProbability -> CategoricalProbability -> Bool
$c/= :: CategoricalProbability -> CategoricalProbability -> Bool
/= :: CategoricalProbability -> CategoricalProbability -> Bool
Eq, Int -> CategoricalProbability -> ShowS
[CategoricalProbability] -> ShowS
CategoricalProbability -> String
(Int -> CategoricalProbability -> ShowS)
-> (CategoricalProbability -> String)
-> ([CategoricalProbability] -> ShowS)
-> Show CategoricalProbability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CategoricalProbability -> ShowS
showsPrec :: Int -> CategoricalProbability -> ShowS
$cshow :: CategoricalProbability -> String
show :: CategoricalProbability -> String
$cshowList :: [CategoricalProbability] -> ShowS
showList :: [CategoricalProbability] -> ShowS
Show)
uniformCP :: CategoricalProbability
uniformCP :: CategoricalProbability
uniformCP = [(Double, Int)] -> Double -> CategoricalProbability
CPBiasedUniform [] Double
1
data GarbageOpts = GarbageOpts
{ GarbageOpts -> Maybe (Vector Word32)
_goSeed :: !(Maybe (VU.Vector Word32)),
GarbageOpts -> GarbageConfigOpts
_goConfig :: !GarbageConfigOpts,
GarbageOpts -> GarbagePrimitiveOpts
_goPrimitive :: !GarbagePrimitiveOpts,
GarbageOpts -> GarbageModuleOpts
_goModule :: !GarbageModuleOpts,
GarbageOpts -> GarbageSpecifyOpts
_goSpecify :: !GarbageSpecifyOpts,
GarbageOpts -> GarbageGenerateOpts
_goGenerate :: !GarbageGenerateOpts,
GarbageOpts -> GarbageTypeOpts
_goType :: !GarbageTypeOpts,
GarbageOpts -> GarbageStatementOpts
_goStatement :: !GarbageStatementOpts,
GarbageOpts -> GarbageExprOpts
_goExpr :: !GarbageExprOpts,
GarbageOpts -> GarbageIdentifierOpts
_goIdentifier :: !GarbageIdentifierOpts,
GarbageOpts -> CategoricalProbability
_goDriveStrength :: !CategoricalProbability,
GarbageOpts -> NumberProbability
_goLValues :: !NumberProbability,
GarbageOpts -> Double
_goOptionalLValue :: !Double,
GarbageOpts -> NumberProbability
_goAttributes :: !NumberProbability,
GarbageOpts -> Double
_goAttributeOptionalValue :: !Double,
GarbageOpts -> CategoricalProbability
_goDelay :: !CategoricalProbability,
GarbageOpts -> CategoricalProbability
_goIntRealIdent :: !CategoricalProbability,
GarbageOpts -> NumberProbability
_goPathDepth :: !NumberProbability,
GarbageOpts -> Double
_goBareMinTypMax :: !Double
}
deriving (GarbageOpts -> GarbageOpts -> Bool
(GarbageOpts -> GarbageOpts -> Bool)
-> (GarbageOpts -> GarbageOpts -> Bool) -> Eq GarbageOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageOpts -> GarbageOpts -> Bool
== :: GarbageOpts -> GarbageOpts -> Bool
$c/= :: GarbageOpts -> GarbageOpts -> Bool
/= :: GarbageOpts -> GarbageOpts -> Bool
Eq, Int -> GarbageOpts -> ShowS
[GarbageOpts] -> ShowS
GarbageOpts -> String
(Int -> GarbageOpts -> ShowS)
-> (GarbageOpts -> String)
-> ([GarbageOpts] -> ShowS)
-> Show GarbageOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageOpts -> ShowS
showsPrec :: Int -> GarbageOpts -> ShowS
$cshow :: GarbageOpts -> String
show :: GarbageOpts -> String
$cshowList :: [GarbageOpts] -> ShowS
showList :: [GarbageOpts] -> ShowS
Show)
data GarbageConfigOpts = GarbageConfigOpts
{ GarbageConfigOpts -> NumberProbability
_gcoBlocks :: !NumberProbability,
GarbageConfigOpts -> NumberProbability
_gcoDesigns :: !NumberProbability,
GarbageConfigOpts -> NumberProbability
_gcoItems :: !NumberProbability,
GarbageConfigOpts -> NumberProbability
_gcoLibraries :: !NumberProbability,
GarbageConfigOpts -> Double
_gcoCell_Inst :: !Double,
GarbageConfigOpts -> Double
_gcoLiblist_Use :: !Double,
GarbageConfigOpts -> Double
_gcoConfig :: !Double,
GarbageConfigOpts -> Double
_gcoLibraryScope :: !Double
}
deriving (GarbageConfigOpts -> GarbageConfigOpts -> Bool
(GarbageConfigOpts -> GarbageConfigOpts -> Bool)
-> (GarbageConfigOpts -> GarbageConfigOpts -> Bool)
-> Eq GarbageConfigOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageConfigOpts -> GarbageConfigOpts -> Bool
== :: GarbageConfigOpts -> GarbageConfigOpts -> Bool
$c/= :: GarbageConfigOpts -> GarbageConfigOpts -> Bool
/= :: GarbageConfigOpts -> GarbageConfigOpts -> Bool
Eq, Int -> GarbageConfigOpts -> ShowS
[GarbageConfigOpts] -> ShowS
GarbageConfigOpts -> String
(Int -> GarbageConfigOpts -> ShowS)
-> (GarbageConfigOpts -> String)
-> ([GarbageConfigOpts] -> ShowS)
-> Show GarbageConfigOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageConfigOpts -> ShowS
showsPrec :: Int -> GarbageConfigOpts -> ShowS
$cshow :: GarbageConfigOpts -> String
show :: GarbageConfigOpts -> String
$cshowList :: [GarbageConfigOpts] -> ShowS
showList :: [GarbageConfigOpts] -> ShowS
Show)
data GarbagePrimitiveOpts = GarbagePrimitiveOpts
{ GarbagePrimitiveOpts -> NumberProbability
_gpoBlocks :: !NumberProbability,
GarbagePrimitiveOpts -> NumberProbability
_gpoPorts :: !NumberProbability,
GarbagePrimitiveOpts -> CategoricalProbability
_gpoPortType :: !CategoricalProbability,
GarbagePrimitiveOpts -> Double
_gpoSeq_Comb :: !Double,
GarbagePrimitiveOpts -> Double
_gpoRegInit :: !Double,
GarbagePrimitiveOpts -> CategoricalProbability
_gpoCombInit :: !CategoricalProbability,
GarbagePrimitiveOpts -> NumberProbability
_gpoTableRows :: !NumberProbability,
GarbagePrimitiveOpts -> CategoricalProbability
_gpoInLevel :: !CategoricalProbability,
GarbagePrimitiveOpts -> CategoricalProbability
_gpoOutLevel :: !CategoricalProbability,
GarbagePrimitiveOpts -> Double
_gpoEdgeSensitive :: !Double,
GarbagePrimitiveOpts -> CategoricalProbability
_gpoEdgeSimplePosNeg :: !CategoricalProbability,
GarbagePrimitiveOpts -> Double
_gpoOutputNoChange :: !Double
}
deriving (GarbagePrimitiveOpts -> GarbagePrimitiveOpts -> Bool
(GarbagePrimitiveOpts -> GarbagePrimitiveOpts -> Bool)
-> (GarbagePrimitiveOpts -> GarbagePrimitiveOpts -> Bool)
-> Eq GarbagePrimitiveOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbagePrimitiveOpts -> GarbagePrimitiveOpts -> Bool
== :: GarbagePrimitiveOpts -> GarbagePrimitiveOpts -> Bool
$c/= :: GarbagePrimitiveOpts -> GarbagePrimitiveOpts -> Bool
/= :: GarbagePrimitiveOpts -> GarbagePrimitiveOpts -> Bool
Eq, Int -> GarbagePrimitiveOpts -> ShowS
[GarbagePrimitiveOpts] -> ShowS
GarbagePrimitiveOpts -> String
(Int -> GarbagePrimitiveOpts -> ShowS)
-> (GarbagePrimitiveOpts -> String)
-> ([GarbagePrimitiveOpts] -> ShowS)
-> Show GarbagePrimitiveOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbagePrimitiveOpts -> ShowS
showsPrec :: Int -> GarbagePrimitiveOpts -> ShowS
$cshow :: GarbagePrimitiveOpts -> String
show :: GarbagePrimitiveOpts -> String
$cshowList :: [GarbagePrimitiveOpts] -> ShowS
showList :: [GarbagePrimitiveOpts] -> ShowS
Show)
data GarbageModuleOpts = GarbageModuleOpts
{ GarbageModuleOpts -> NumberProbability
_gmoBlocks :: !NumberProbability,
GarbageModuleOpts -> Double
_gmoNamed_Positional :: !Double,
GarbageModuleOpts -> NumberProbability
_gmoParameters :: !NumberProbability,
GarbageModuleOpts -> Double
_gmoOptionalParameter :: !Double,
GarbageModuleOpts -> NumberProbability
_gmoPorts :: !NumberProbability,
GarbageModuleOpts -> NumberProbability
_gmoPortLValues :: !NumberProbability,
GarbageModuleOpts -> Double
_gmoPortRange :: !Double,
GarbageModuleOpts -> CategoricalProbability
_gmoPortDir :: !CategoricalProbability,
GarbageModuleOpts -> Double
_gmoOptionalPort :: !Double,
GarbageModuleOpts -> NumberProbability
_gmoItems :: !NumberProbability,
GarbageModuleOpts -> CategoricalProbability
_gmoItem :: !CategoricalProbability,
GarbageModuleOpts -> Double
_gmoTimeScale :: !Double,
GarbageModuleOpts -> CategoricalProbability
_gmoTimeMagnitude :: !CategoricalProbability,
GarbageModuleOpts -> Double
_gmoCell :: !Double,
GarbageModuleOpts -> CategoricalProbability
_gmoUnconnectedDrive :: !CategoricalProbability,
GarbageModuleOpts -> CategoricalProbability
_gmoDefaultNetType :: !CategoricalProbability,
:: !Bool
}
deriving (GarbageModuleOpts -> GarbageModuleOpts -> Bool
(GarbageModuleOpts -> GarbageModuleOpts -> Bool)
-> (GarbageModuleOpts -> GarbageModuleOpts -> Bool)
-> Eq GarbageModuleOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageModuleOpts -> GarbageModuleOpts -> Bool
== :: GarbageModuleOpts -> GarbageModuleOpts -> Bool
$c/= :: GarbageModuleOpts -> GarbageModuleOpts -> Bool
/= :: GarbageModuleOpts -> GarbageModuleOpts -> Bool
Eq, Int -> GarbageModuleOpts -> ShowS
[GarbageModuleOpts] -> ShowS
GarbageModuleOpts -> String
(Int -> GarbageModuleOpts -> ShowS)
-> (GarbageModuleOpts -> String)
-> ([GarbageModuleOpts] -> ShowS)
-> Show GarbageModuleOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageModuleOpts -> ShowS
showsPrec :: Int -> GarbageModuleOpts -> ShowS
$cshow :: GarbageModuleOpts -> String
show :: GarbageModuleOpts -> String
$cshowList :: [GarbageModuleOpts] -> ShowS
showList :: [GarbageModuleOpts] -> ShowS
Show)
data GarbageSpecifyOpts = GarbageSpecifyOpts
{ GarbageSpecifyOpts -> GarbageSpecifyPathOpts
_gsyoPath :: !GarbageSpecifyPathOpts,
GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts
_gsyoTimingCheck :: !GarbageSpecifyTimingCheckOpts,
GarbageSpecifyOpts -> NumberProbability
_gsyoItems :: !NumberProbability,
GarbageSpecifyOpts -> CategoricalProbability
_gsyoItem :: !CategoricalProbability,
GarbageSpecifyOpts -> Double
_gsyoTermRange :: !Double,
GarbageSpecifyOpts -> Double
_gsyoParamRange :: !Double,
GarbageSpecifyOpts -> Double
_gsyoPathPulseEscaped_Simple :: !Double,
GarbageSpecifyOpts -> Double
_gsyoPathPulseRange :: !Double
}
deriving (GarbageSpecifyOpts -> GarbageSpecifyOpts -> Bool
(GarbageSpecifyOpts -> GarbageSpecifyOpts -> Bool)
-> (GarbageSpecifyOpts -> GarbageSpecifyOpts -> Bool)
-> Eq GarbageSpecifyOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageSpecifyOpts -> GarbageSpecifyOpts -> Bool
== :: GarbageSpecifyOpts -> GarbageSpecifyOpts -> Bool
$c/= :: GarbageSpecifyOpts -> GarbageSpecifyOpts -> Bool
/= :: GarbageSpecifyOpts -> GarbageSpecifyOpts -> Bool
Eq, Int -> GarbageSpecifyOpts -> ShowS
[GarbageSpecifyOpts] -> ShowS
GarbageSpecifyOpts -> String
(Int -> GarbageSpecifyOpts -> ShowS)
-> (GarbageSpecifyOpts -> String)
-> ([GarbageSpecifyOpts] -> ShowS)
-> Show GarbageSpecifyOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageSpecifyOpts -> ShowS
showsPrec :: Int -> GarbageSpecifyOpts -> ShowS
$cshow :: GarbageSpecifyOpts -> String
show :: GarbageSpecifyOpts -> String
$cshowList :: [GarbageSpecifyOpts] -> ShowS
showList :: [GarbageSpecifyOpts] -> ShowS
Show)
data GarbageSpecifyPathOpts = GarbageSpecifyPathOpts
{ GarbageSpecifyPathOpts -> CategoricalProbability
_gspoCondition :: !CategoricalProbability,
GarbageSpecifyPathOpts -> Double
_gspoFull_Parallel :: !Double,
GarbageSpecifyPathOpts -> Double
_gspoEdgeSensitive :: !Double,
GarbageSpecifyPathOpts -> NumberProbability
_gspoFullSources :: !NumberProbability,
GarbageSpecifyPathOpts -> NumberProbability
_gspoFullDestinations :: !NumberProbability,
GarbageSpecifyPathOpts -> CategoricalProbability
_gspoPolarity :: !CategoricalProbability,
GarbageSpecifyPathOpts -> CategoricalProbability
_gspoEdgeSensitivity :: !CategoricalProbability,
GarbageSpecifyPathOpts -> CategoricalProbability
_gspoDelayKind :: !CategoricalProbability
}
deriving (GarbageSpecifyPathOpts -> GarbageSpecifyPathOpts -> Bool
(GarbageSpecifyPathOpts -> GarbageSpecifyPathOpts -> Bool)
-> (GarbageSpecifyPathOpts -> GarbageSpecifyPathOpts -> Bool)
-> Eq GarbageSpecifyPathOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageSpecifyPathOpts -> GarbageSpecifyPathOpts -> Bool
== :: GarbageSpecifyPathOpts -> GarbageSpecifyPathOpts -> Bool
$c/= :: GarbageSpecifyPathOpts -> GarbageSpecifyPathOpts -> Bool
/= :: GarbageSpecifyPathOpts -> GarbageSpecifyPathOpts -> Bool
Eq, Int -> GarbageSpecifyPathOpts -> ShowS
[GarbageSpecifyPathOpts] -> ShowS
GarbageSpecifyPathOpts -> String
(Int -> GarbageSpecifyPathOpts -> ShowS)
-> (GarbageSpecifyPathOpts -> String)
-> ([GarbageSpecifyPathOpts] -> ShowS)
-> Show GarbageSpecifyPathOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageSpecifyPathOpts -> ShowS
showsPrec :: Int -> GarbageSpecifyPathOpts -> ShowS
$cshow :: GarbageSpecifyPathOpts -> String
show :: GarbageSpecifyPathOpts -> String
$cshowList :: [GarbageSpecifyPathOpts] -> ShowS
showList :: [GarbageSpecifyPathOpts] -> ShowS
Show)
data GarbageSpecifyTimingCheckOpts = GarbageSpecifyTimingCheckOpts
{ GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg :: !Double,
GarbageSpecifyTimingCheckOpts -> Double
_gstcoEvent :: !Double,
GarbageSpecifyTimingCheckOpts -> Double
_gstcoEventEdge :: !Double,
GarbageSpecifyTimingCheckOpts -> Double
_gstcoCondition :: !Double,
GarbageSpecifyTimingCheckOpts -> Double
_gstcoCondNeg_Pos :: !Double,
GarbageSpecifyTimingCheckOpts -> Double
_gstcoDelayedMinTypMax :: !Double
}
deriving (GarbageSpecifyTimingCheckOpts
-> GarbageSpecifyTimingCheckOpts -> Bool
(GarbageSpecifyTimingCheckOpts
-> GarbageSpecifyTimingCheckOpts -> Bool)
-> (GarbageSpecifyTimingCheckOpts
-> GarbageSpecifyTimingCheckOpts -> Bool)
-> Eq GarbageSpecifyTimingCheckOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageSpecifyTimingCheckOpts
-> GarbageSpecifyTimingCheckOpts -> Bool
== :: GarbageSpecifyTimingCheckOpts
-> GarbageSpecifyTimingCheckOpts -> Bool
$c/= :: GarbageSpecifyTimingCheckOpts
-> GarbageSpecifyTimingCheckOpts -> Bool
/= :: GarbageSpecifyTimingCheckOpts
-> GarbageSpecifyTimingCheckOpts -> Bool
Eq, Int -> GarbageSpecifyTimingCheckOpts -> ShowS
[GarbageSpecifyTimingCheckOpts] -> ShowS
GarbageSpecifyTimingCheckOpts -> String
(Int -> GarbageSpecifyTimingCheckOpts -> ShowS)
-> (GarbageSpecifyTimingCheckOpts -> String)
-> ([GarbageSpecifyTimingCheckOpts] -> ShowS)
-> Show GarbageSpecifyTimingCheckOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageSpecifyTimingCheckOpts -> ShowS
showsPrec :: Int -> GarbageSpecifyTimingCheckOpts -> ShowS
$cshow :: GarbageSpecifyTimingCheckOpts -> String
show :: GarbageSpecifyTimingCheckOpts -> String
$cshowList :: [GarbageSpecifyTimingCheckOpts] -> ShowS
showList :: [GarbageSpecifyTimingCheckOpts] -> ShowS
Show)
data GarbageGenerateOpts = GarbageGenerateOpts
{ GarbageGenerateOpts -> GarbageAttenuationOpts
_ggoAttenuation :: !GarbageAttenuationOpts,
GarbageGenerateOpts -> NumberProbability
_ggoItems :: !NumberProbability,
GarbageGenerateOpts -> CategoricalProbability
_ggoItem :: !CategoricalProbability,
GarbageGenerateOpts -> Double
_ggoOptionalBlock :: !Double,
GarbageGenerateOpts -> Double
_ggoInstOptionalDelay :: !Double,
GarbageGenerateOpts -> Double
_ggoInstOptionalRange :: !Double,
GarbageGenerateOpts -> Double
_ggoPrimitiveOptIdent :: !Double,
GarbageGenerateOpts -> CategoricalProbability
_ggoCondBlock :: !CategoricalProbability,
GarbageGenerateOpts -> CategoricalProbability
_ggoNetType :: !CategoricalProbability,
GarbageGenerateOpts -> Double
_ggoNetRange :: !Double,
GarbageGenerateOpts -> CategoricalProbability
_ggoNetVectoring :: !CategoricalProbability,
GarbageGenerateOpts -> CategoricalProbability
_ggoDeclItem :: !CategoricalProbability,
GarbageGenerateOpts -> Double
_ggoDeclDim_Init :: !Double,
GarbageGenerateOpts -> CategoricalProbability
_ggoChargeStrength :: !CategoricalProbability,
GarbageGenerateOpts -> Double
_ggoTaskFunAutomatic :: !Double,
GarbageGenerateOpts -> CategoricalProbability
_ggoTaskFunDecl :: !CategoricalProbability,
GarbageGenerateOpts -> Double
_ggoTaskFunRegister :: !Double,
GarbageGenerateOpts -> NumberProbability
_ggoTaskFunPorts :: !NumberProbability,
GarbageGenerateOpts -> CategoricalProbability
_ggoTaskFunPortType :: !CategoricalProbability,
GarbageGenerateOpts -> CategoricalProbability
_ggoTaskPortDirection :: !CategoricalProbability,
GarbageGenerateOpts -> Double
_ggoFunRetType :: !Double,
GarbageGenerateOpts -> CategoricalProbability
_ggoGateInst :: !CategoricalProbability,
GarbageGenerateOpts -> Double
_ggoGateOptIdent :: !Double,
GarbageGenerateOpts -> CategoricalProbability
_ggoGateNInputType :: !CategoricalProbability,
GarbageGenerateOpts -> NumberProbability
_ggoGateInputs :: !NumberProbability,
GarbageGenerateOpts -> NumberProbability
_ggoGateOutputs :: !NumberProbability,
GarbageGenerateOpts -> NumberProbability
_ggoCaseBranches :: !NumberProbability,
GarbageGenerateOpts -> NumberProbability
_ggoCaseBranchPatterns :: !NumberProbability
}
deriving (GarbageGenerateOpts -> GarbageGenerateOpts -> Bool
(GarbageGenerateOpts -> GarbageGenerateOpts -> Bool)
-> (GarbageGenerateOpts -> GarbageGenerateOpts -> Bool)
-> Eq GarbageGenerateOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageGenerateOpts -> GarbageGenerateOpts -> Bool
== :: GarbageGenerateOpts -> GarbageGenerateOpts -> Bool
$c/= :: GarbageGenerateOpts -> GarbageGenerateOpts -> Bool
/= :: GarbageGenerateOpts -> GarbageGenerateOpts -> Bool
Eq, Int -> GarbageGenerateOpts -> ShowS
[GarbageGenerateOpts] -> ShowS
GarbageGenerateOpts -> String
(Int -> GarbageGenerateOpts -> ShowS)
-> (GarbageGenerateOpts -> String)
-> ([GarbageGenerateOpts] -> ShowS)
-> Show GarbageGenerateOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageGenerateOpts -> ShowS
showsPrec :: Int -> GarbageGenerateOpts -> ShowS
$cshow :: GarbageGenerateOpts -> String
show :: GarbageGenerateOpts -> String
$cshowList :: [GarbageGenerateOpts] -> ShowS
showList :: [GarbageGenerateOpts] -> ShowS
Show)
data GarbageTypeOpts = GarbageTypeOpts
{ GarbageTypeOpts -> Double
_gtoAbstract_Concrete :: !Double,
GarbageTypeOpts -> CategoricalProbability
_gtoAbstract :: !CategoricalProbability,
GarbageTypeOpts -> Double
_gtoConcreteSignedness :: !Double,
GarbageTypeOpts -> Double
_gtoConcreteBitRange :: !Double,
GarbageTypeOpts -> NumberProbability
_gtoDimensions :: !NumberProbability
}
deriving (GarbageTypeOpts -> GarbageTypeOpts -> Bool
(GarbageTypeOpts -> GarbageTypeOpts -> Bool)
-> (GarbageTypeOpts -> GarbageTypeOpts -> Bool)
-> Eq GarbageTypeOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageTypeOpts -> GarbageTypeOpts -> Bool
== :: GarbageTypeOpts -> GarbageTypeOpts -> Bool
$c/= :: GarbageTypeOpts -> GarbageTypeOpts -> Bool
/= :: GarbageTypeOpts -> GarbageTypeOpts -> Bool
Eq, Int -> GarbageTypeOpts -> ShowS
[GarbageTypeOpts] -> ShowS
GarbageTypeOpts -> String
(Int -> GarbageTypeOpts -> ShowS)
-> (GarbageTypeOpts -> String)
-> ([GarbageTypeOpts] -> ShowS)
-> Show GarbageTypeOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageTypeOpts -> ShowS
showsPrec :: Int -> GarbageTypeOpts -> ShowS
$cshow :: GarbageTypeOpts -> String
show :: GarbageTypeOpts -> String
$cshowList :: [GarbageTypeOpts] -> ShowS
showList :: [GarbageTypeOpts] -> ShowS
Show)
data GarbageAttenuationOpts = GarbageAttenuationOpts
{ GarbageAttenuationOpts -> Double
_gaoCurrent :: !Double,
GarbageAttenuationOpts -> Double
_gaoDecrease :: !Double
}
deriving (GarbageAttenuationOpts -> GarbageAttenuationOpts -> Bool
(GarbageAttenuationOpts -> GarbageAttenuationOpts -> Bool)
-> (GarbageAttenuationOpts -> GarbageAttenuationOpts -> Bool)
-> Eq GarbageAttenuationOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageAttenuationOpts -> GarbageAttenuationOpts -> Bool
== :: GarbageAttenuationOpts -> GarbageAttenuationOpts -> Bool
$c/= :: GarbageAttenuationOpts -> GarbageAttenuationOpts -> Bool
/= :: GarbageAttenuationOpts -> GarbageAttenuationOpts -> Bool
Eq, Int -> GarbageAttenuationOpts -> ShowS
[GarbageAttenuationOpts] -> ShowS
GarbageAttenuationOpts -> String
(Int -> GarbageAttenuationOpts -> ShowS)
-> (GarbageAttenuationOpts -> String)
-> ([GarbageAttenuationOpts] -> ShowS)
-> Show GarbageAttenuationOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageAttenuationOpts -> ShowS
showsPrec :: Int -> GarbageAttenuationOpts -> ShowS
$cshow :: GarbageAttenuationOpts -> String
show :: GarbageAttenuationOpts -> String
$cshowList :: [GarbageAttenuationOpts] -> ShowS
showList :: [GarbageAttenuationOpts] -> ShowS
Show)
data GarbageStatementOpts = GarbageStatementOpts
{ GarbageStatementOpts -> GarbageAttenuationOpts
_gstoAttenuation :: !GarbageAttenuationOpts,
GarbageStatementOpts -> Double
_gstoOptional :: !Double,
GarbageStatementOpts -> CategoricalProbability
_gstoItem :: !CategoricalProbability,
GarbageStatementOpts -> NumberProbability
_gstoItems :: !NumberProbability,
GarbageStatementOpts -> Double
_gstoOptionalDelEvCtl :: !Double,
GarbageStatementOpts -> Double
_gstoAssignmentBlocking :: !Double,
GarbageStatementOpts -> CategoricalProbability
_gstoCase :: !CategoricalProbability,
GarbageStatementOpts -> NumberProbability
_gstoCaseBranches :: !NumberProbability,
GarbageStatementOpts -> NumberProbability
_gstoCaseBranchPatterns :: !NumberProbability,
GarbageStatementOpts -> CategoricalProbability
_gstoLoop :: !CategoricalProbability,
GarbageStatementOpts -> Double
_gstoBlockPar_Seq :: !Double,
:: !Double,
GarbageStatementOpts -> NumberProbability
_gstoBlockDecls :: !NumberProbability,
GarbageStatementOpts -> CategoricalProbability
_gstoBlockDecl :: !CategoricalProbability,
GarbageStatementOpts -> CategoricalProbability
_gstoProcContAssign :: !CategoricalProbability,
GarbageStatementOpts -> Double
_gstoPCAVar_Net :: !Double,
GarbageStatementOpts -> CategoricalProbability
_gstoDelayEventRepeat :: !CategoricalProbability,
GarbageStatementOpts -> CategoricalProbability
_gstoEvent :: !CategoricalProbability,
GarbageStatementOpts -> NumberProbability
_gstoEvents :: !NumberProbability,
GarbageStatementOpts -> CategoricalProbability
_gstoEventPrefix :: !CategoricalProbability,
GarbageStatementOpts -> NumberProbability
_gstoSysTaskPorts :: !NumberProbability,
GarbageStatementOpts -> Double
_gstoSysTaskOptionalPort :: !Double
}
deriving (GarbageStatementOpts -> GarbageStatementOpts -> Bool
(GarbageStatementOpts -> GarbageStatementOpts -> Bool)
-> (GarbageStatementOpts -> GarbageStatementOpts -> Bool)
-> Eq GarbageStatementOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageStatementOpts -> GarbageStatementOpts -> Bool
== :: GarbageStatementOpts -> GarbageStatementOpts -> Bool
$c/= :: GarbageStatementOpts -> GarbageStatementOpts -> Bool
/= :: GarbageStatementOpts -> GarbageStatementOpts -> Bool
Eq, Int -> GarbageStatementOpts -> ShowS
[GarbageStatementOpts] -> ShowS
GarbageStatementOpts -> String
(Int -> GarbageStatementOpts -> ShowS)
-> (GarbageStatementOpts -> String)
-> ([GarbageStatementOpts] -> ShowS)
-> Show GarbageStatementOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageStatementOpts -> ShowS
showsPrec :: Int -> GarbageStatementOpts -> ShowS
$cshow :: GarbageStatementOpts -> String
show :: GarbageStatementOpts -> String
$cshowList :: [GarbageStatementOpts] -> ShowS
showList :: [GarbageStatementOpts] -> ShowS
Show)
data GarbageExprOpts = GarbageExprOpts
{ GarbageExprOpts -> GarbageAttenuationOpts
_geoAttenuation :: !GarbageAttenuationOpts,
GarbageExprOpts -> CategoricalProbability
_geoItem :: !CategoricalProbability,
GarbageExprOpts -> CategoricalProbability
_geoPrimary :: !CategoricalProbability,
GarbageExprOpts -> CategoricalProbability
_geoUnary :: !CategoricalProbability,
GarbageExprOpts -> CategoricalProbability
_geoBinary :: !CategoricalProbability,
GarbageExprOpts -> Double
_geoMinTypMax :: !Double,
GarbageExprOpts -> Double
_geoDimRange :: !Double,
GarbageExprOpts -> CategoricalProbability
_geoRange :: !CategoricalProbability,
GarbageExprOpts -> Double
_geoRangeOffsetPos_Neg :: !Double,
GarbageExprOpts -> NumberProbability
_geoConcatenations :: !NumberProbability,
GarbageExprOpts -> NumberProbability
_geoSysFunArgs :: !NumberProbability,
GarbageExprOpts -> CategoricalProbability
_geoLiteralWidth :: !CategoricalProbability,
GarbageExprOpts -> Double
_geoLiteralSigned :: !Double,
GarbageExprOpts -> NumberProbability
_geoStringCharacters :: !NumberProbability,
GarbageExprOpts -> CategoricalProbability
_geoStringCharacter :: !CategoricalProbability,
GarbageExprOpts -> Double
_geoFixed_Floating :: !Double,
GarbageExprOpts -> CategoricalProbability
_geoExponentSign :: !CategoricalProbability,
GarbageExprOpts -> Double
_geoX_Z :: !Double,
GarbageExprOpts -> NumberProbability
_geoBinarySymbols :: !NumberProbability,
GarbageExprOpts -> CategoricalProbability
_geoBinarySymbol :: !CategoricalProbability,
GarbageExprOpts -> NumberProbability
_geoOctalSymbols :: !NumberProbability,
GarbageExprOpts -> CategoricalProbability
_geoOctalSymbol :: !CategoricalProbability,
GarbageExprOpts -> NumberProbability
_geoDecimalSymbols :: !NumberProbability,
GarbageExprOpts -> CategoricalProbability
_geoDecimalSymbol :: !CategoricalProbability,
GarbageExprOpts -> NumberProbability
_geoHexadecimalSymbols :: !NumberProbability,
GarbageExprOpts -> CategoricalProbability
_geoHexadecimalSymbol :: !CategoricalProbability
}
deriving (GarbageExprOpts -> GarbageExprOpts -> Bool
(GarbageExprOpts -> GarbageExprOpts -> Bool)
-> (GarbageExprOpts -> GarbageExprOpts -> Bool)
-> Eq GarbageExprOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageExprOpts -> GarbageExprOpts -> Bool
== :: GarbageExprOpts -> GarbageExprOpts -> Bool
$c/= :: GarbageExprOpts -> GarbageExprOpts -> Bool
/= :: GarbageExprOpts -> GarbageExprOpts -> Bool
Eq, Int -> GarbageExprOpts -> ShowS
[GarbageExprOpts] -> ShowS
GarbageExprOpts -> String
(Int -> GarbageExprOpts -> ShowS)
-> (GarbageExprOpts -> String)
-> ([GarbageExprOpts] -> ShowS)
-> Show GarbageExprOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageExprOpts -> ShowS
showsPrec :: Int -> GarbageExprOpts -> ShowS
$cshow :: GarbageExprOpts -> String
show :: GarbageExprOpts -> String
$cshowList :: [GarbageExprOpts] -> ShowS
showList :: [GarbageExprOpts] -> ShowS
Show)
data GarbageIdentifierOpts = GarbageIdentifierOpts
{ GarbageIdentifierOpts -> Double
_gioEscaped_Simple :: !Double,
GarbageIdentifierOpts -> NumberProbability
_gioSimpleLetters :: !NumberProbability,
GarbageIdentifierOpts -> CategoricalProbability
_gioSimpleLetter :: !CategoricalProbability,
GarbageIdentifierOpts -> NumberProbability
_gioEscapedLetters :: !NumberProbability,
GarbageIdentifierOpts -> CategoricalProbability
_gioEscapedLetter :: !CategoricalProbability,
GarbageIdentifierOpts -> NumberProbability
_gioSystemLetters :: !NumberProbability,
GarbageIdentifierOpts -> CategoricalProbability
_gioSystemFirstLetter :: !CategoricalProbability
}
deriving (GarbageIdentifierOpts -> GarbageIdentifierOpts -> Bool
(GarbageIdentifierOpts -> GarbageIdentifierOpts -> Bool)
-> (GarbageIdentifierOpts -> GarbageIdentifierOpts -> Bool)
-> Eq GarbageIdentifierOpts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GarbageIdentifierOpts -> GarbageIdentifierOpts -> Bool
== :: GarbageIdentifierOpts -> GarbageIdentifierOpts -> Bool
$c/= :: GarbageIdentifierOpts -> GarbageIdentifierOpts -> Bool
/= :: GarbageIdentifierOpts -> GarbageIdentifierOpts -> Bool
Eq, Int -> GarbageIdentifierOpts -> ShowS
[GarbageIdentifierOpts] -> ShowS
GarbageIdentifierOpts -> String
(Int -> GarbageIdentifierOpts -> ShowS)
-> (GarbageIdentifierOpts -> String)
-> ([GarbageIdentifierOpts] -> ShowS)
-> Show GarbageIdentifierOpts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GarbageIdentifierOpts -> ShowS
showsPrec :: Int -> GarbageIdentifierOpts -> ShowS
$cshow :: GarbageIdentifierOpts -> String
show :: GarbageIdentifierOpts -> String
$cshowList :: [GarbageIdentifierOpts] -> ShowS
showList :: [GarbageIdentifierOpts] -> ShowS
Show)
defAttenuationOpts :: GarbageAttenuationOpts
defAttenuationOpts :: GarbageAttenuationOpts
defAttenuationOpts = Double -> Double -> GarbageAttenuationOpts
GarbageAttenuationOpts Double
1.0 Double
0.7
defGarbageOpts :: GarbageOpts
defGarbageOpts :: GarbageOpts
defGarbageOpts =
GarbageOpts
{ _goSeed :: Maybe (Vector Word32)
_goSeed = Maybe (Vector Word32)
forall a. Maybe a
Nothing,
_goConfig :: GarbageConfigOpts
_goConfig = GarbageConfigOpts
{ _gcoBlocks :: NumberProbability
_gcoBlocks = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gcoDesigns :: NumberProbability
_gcoDesigns = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gcoItems :: NumberProbability
_gcoItems = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gcoLibraries :: NumberProbability
_gcoLibraries = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gcoCell_Inst :: Double
_gcoCell_Inst = Double
0.5,
_gcoLiblist_Use :: Double
_gcoLiblist_Use = Double
0.5,
_gcoConfig :: Double
_gcoConfig = Double
0.5,
_gcoLibraryScope :: Double
_gcoLibraryScope = Double
0.5
},
_goPrimitive :: GarbagePrimitiveOpts
_goPrimitive = GarbagePrimitiveOpts
{ _gpoBlocks :: NumberProbability
_gpoBlocks = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
2,
_gpoPorts :: NumberProbability
_gpoPorts = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_gpoPortType :: CategoricalProbability
_gpoPortType = CategoricalProbability
uniformCP,
_gpoSeq_Comb :: Double
_gpoSeq_Comb = Double
0.5,
_gpoRegInit :: Double
_gpoRegInit = Double
0.5,
_gpoCombInit :: CategoricalProbability
_gpoCombInit = CategoricalProbability
uniformCP,
_gpoTableRows :: NumberProbability
_gpoTableRows = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
4,
_gpoInLevel :: CategoricalProbability
_gpoInLevel = CategoricalProbability
uniformCP,
_gpoOutLevel :: CategoricalProbability
_gpoOutLevel = CategoricalProbability
uniformCP,
_gpoEdgeSensitive :: Double
_gpoEdgeSensitive = Double
0.5,
_gpoEdgeSimplePosNeg :: CategoricalProbability
_gpoEdgeSimplePosNeg = CategoricalProbability
uniformCP,
_gpoOutputNoChange :: Double
_gpoOutputNoChange = Double
0.5
},
_goModule :: GarbageModuleOpts
_goModule = GarbageModuleOpts
{ _gmoBlocks :: NumberProbability
_gmoBlocks = Int -> Double -> NumberProbability
NPPoisson Int
1 Double
2,
_gmoNamed_Positional :: Double
_gmoNamed_Positional = Double
0.5,
_gmoParameters :: NumberProbability
_gmoParameters = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_gmoOptionalParameter :: Double
_gmoOptionalParameter = Double
0.5,
_gmoPorts :: NumberProbability
_gmoPorts = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_gmoPortLValues :: NumberProbability
_gmoPortLValues = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_gmoPortRange :: Double
_gmoPortRange = Double
0.5,
_gmoPortDir :: CategoricalProbability
_gmoPortDir = CategoricalProbability
uniformCP,
_gmoOptionalPort :: Double
_gmoOptionalPort = Double
0.5,
_gmoItems :: NumberProbability
_gmoItems = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
3,
_gmoItem :: CategoricalProbability
_gmoItem = NonEmpty Double -> CategoricalProbability
CPDiscrete [Double
Item (NonEmpty Double)
6, Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
3, Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
1],
_gmoTimeScale :: Double
_gmoTimeScale = Double
0.5,
_gmoTimeMagnitude :: CategoricalProbability
_gmoTimeMagnitude = CategoricalProbability
uniformCP,
_gmoCell :: Double
_gmoCell = Double
0.5,
_gmoUnconnectedDrive :: CategoricalProbability
_gmoUnconnectedDrive = CategoricalProbability
uniformCP,
_gmoDefaultNetType :: CategoricalProbability
_gmoDefaultNetType = CategoricalProbability
uniformCP,
_gmoNonAsciiHeader :: Bool
_gmoNonAsciiHeader = Bool
True
},
_goSpecify :: GarbageSpecifyOpts
_goSpecify = GarbageSpecifyOpts
{ _gsyoPath :: GarbageSpecifyPathOpts
_gsyoPath = GarbageSpecifyPathOpts
{ _gspoCondition :: CategoricalProbability
_gspoCondition = CategoricalProbability
uniformCP,
_gspoFull_Parallel :: Double
_gspoFull_Parallel = Double
0.5,
_gspoEdgeSensitive :: Double
_gspoEdgeSensitive = Double
0.5,
_gspoFullSources :: NumberProbability
_gspoFullSources = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gspoFullDestinations :: NumberProbability
_gspoFullDestinations = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gspoPolarity :: CategoricalProbability
_gspoPolarity = CategoricalProbability
uniformCP,
_gspoEdgeSensitivity :: CategoricalProbability
_gspoEdgeSensitivity = CategoricalProbability
uniformCP,
_gspoDelayKind :: CategoricalProbability
_gspoDelayKind = CategoricalProbability
uniformCP
},
_gsyoTimingCheck :: GarbageSpecifyTimingCheckOpts
_gsyoTimingCheck = GarbageSpecifyTimingCheckOpts
{ _gstcoOptionalArg :: Double
_gstcoOptionalArg = Double
0.5,
_gstcoEvent :: Double
_gstcoEvent = Double
0.5,
_gstcoEventEdge :: Double
_gstcoEventEdge = Double
0.25,
_gstcoCondition :: Double
_gstcoCondition = Double
0.5,
_gstcoCondNeg_Pos :: Double
_gstcoCondNeg_Pos = Double
0.5,
_gstcoDelayedMinTypMax :: Double
_gstcoDelayedMinTypMax = Double
0.5
},
_gsyoItems :: NumberProbability
_gsyoItems = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gsyoItem :: CategoricalProbability
_gsyoItem = CategoricalProbability
uniformCP,
_gsyoTermRange :: Double
_gsyoTermRange = Double
0.5,
_gsyoParamRange :: Double
_gsyoParamRange = Double
0.5,
_gsyoPathPulseEscaped_Simple :: Double
_gsyoPathPulseEscaped_Simple = Double
0.5,
_gsyoPathPulseRange :: Double
_gsyoPathPulseRange = Double
0.5
},
_goGenerate :: GarbageGenerateOpts
_goGenerate = GarbageGenerateOpts
{ _ggoAttenuation :: GarbageAttenuationOpts
_ggoAttenuation = GarbageAttenuationOpts
defAttenuationOpts,
_ggoItems :: NumberProbability
_ggoItems = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
3,
_ggoItem :: CategoricalProbability
_ggoItem = CategoricalProbability
uniformCP,
_ggoOptionalBlock :: Double
_ggoOptionalBlock = Double
0.5,
_ggoInstOptionalDelay :: Double
_ggoInstOptionalDelay = Double
0.5,
_ggoInstOptionalRange :: Double
_ggoInstOptionalRange = Double
0.5,
_ggoPrimitiveOptIdent :: Double
_ggoPrimitiveOptIdent = Double
0.5,
_ggoCondBlock :: CategoricalProbability
_ggoCondBlock = CategoricalProbability
uniformCP,
_ggoNetType :: CategoricalProbability
_ggoNetType = CategoricalProbability
uniformCP,
_ggoNetRange :: Double
_ggoNetRange = Double
0.5,
_ggoNetVectoring :: CategoricalProbability
_ggoNetVectoring = CategoricalProbability
uniformCP,
_ggoDeclItem :: CategoricalProbability
_ggoDeclItem = CategoricalProbability
uniformCP,
_ggoDeclDim_Init :: Double
_ggoDeclDim_Init = Double
0.5,
_ggoChargeStrength :: CategoricalProbability
_ggoChargeStrength = CategoricalProbability
uniformCP,
_ggoTaskFunAutomatic :: Double
_ggoTaskFunAutomatic = Double
0.5,
_ggoTaskFunDecl :: CategoricalProbability
_ggoTaskFunDecl = CategoricalProbability
uniformCP,
_ggoTaskFunRegister :: Double
_ggoTaskFunRegister = Double
0.5,
_ggoTaskFunPorts :: NumberProbability
_ggoTaskFunPorts = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_ggoTaskFunPortType :: CategoricalProbability
_ggoTaskFunPortType = CategoricalProbability
uniformCP,
_ggoTaskPortDirection :: CategoricalProbability
_ggoTaskPortDirection = CategoricalProbability
uniformCP,
_ggoFunRetType :: Double
_ggoFunRetType = Double
0.5,
_ggoGateInst :: CategoricalProbability
_ggoGateInst = CategoricalProbability
uniformCP,
_ggoGateOptIdent :: Double
_ggoGateOptIdent = Double
0.5,
_ggoGateNInputType :: CategoricalProbability
_ggoGateNInputType = CategoricalProbability
uniformCP,
_ggoGateInputs :: NumberProbability
_ggoGateInputs = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_ggoGateOutputs :: NumberProbability
_ggoGateOutputs = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_ggoCaseBranches :: NumberProbability
_ggoCaseBranches = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.75 Int
2,
_ggoCaseBranchPatterns :: NumberProbability
_ggoCaseBranchPatterns = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1
},
_goType :: GarbageTypeOpts
_goType = GarbageTypeOpts
{ _gtoAbstract_Concrete :: Double
_gtoAbstract_Concrete = Double
0.5,
_gtoAbstract :: CategoricalProbability
_gtoAbstract = CategoricalProbability
uniformCP,
_gtoConcreteSignedness :: Double
_gtoConcreteSignedness = Double
0.5,
_gtoConcreteBitRange :: Double
_gtoConcreteBitRange = Double
0.5,
_gtoDimensions :: NumberProbability
_gtoDimensions = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
1
},
_goStatement :: GarbageStatementOpts
_goStatement = GarbageStatementOpts
{ _gstoAttenuation :: GarbageAttenuationOpts
_gstoAttenuation = GarbageAttenuationOpts
defAttenuationOpts,
_gstoOptional :: Double
_gstoOptional = Double
0.5,
_gstoItems :: NumberProbability
_gstoItems = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
3,
_gstoItem :: CategoricalProbability
_gstoItem = CategoricalProbability
uniformCP,
_gstoOptionalDelEvCtl :: Double
_gstoOptionalDelEvCtl = Double
0.5,
_gstoAssignmentBlocking :: Double
_gstoAssignmentBlocking = Double
0.5,
_gstoCase :: CategoricalProbability
_gstoCase = CategoricalProbability
uniformCP,
_gstoCaseBranches :: NumberProbability
_gstoCaseBranches = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.75 Int
2,
_gstoCaseBranchPatterns :: NumberProbability
_gstoCaseBranchPatterns = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_gstoLoop :: CategoricalProbability
_gstoLoop = CategoricalProbability
uniformCP,
_gstoBlockPar_Seq :: Double
_gstoBlockPar_Seq = Double
0.5,
_gstoBlockHeader :: Double
_gstoBlockHeader = Double
0.5,
_gstoBlockDecls :: NumberProbability
_gstoBlockDecls = Int -> Double -> NumberProbability
NPPoisson Int
0 Double
1,
_gstoBlockDecl :: CategoricalProbability
_gstoBlockDecl = CategoricalProbability
uniformCP,
_gstoProcContAssign :: CategoricalProbability
_gstoProcContAssign = CategoricalProbability
uniformCP,
_gstoPCAVar_Net :: Double
_gstoPCAVar_Net = Double
0.5,
_gstoDelayEventRepeat :: CategoricalProbability
_gstoDelayEventRepeat = CategoricalProbability
uniformCP,
_gstoEvent :: CategoricalProbability
_gstoEvent = CategoricalProbability
uniformCP,
_gstoEvents :: NumberProbability
_gstoEvents = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
1,
_gstoEventPrefix :: CategoricalProbability
_gstoEventPrefix = CategoricalProbability
uniformCP,
_gstoSysTaskPorts :: NumberProbability
_gstoSysTaskPorts = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_gstoSysTaskOptionalPort :: Double
_gstoSysTaskOptionalPort = Double
0.5
},
_goExpr :: GarbageExprOpts
_goExpr = GarbageExprOpts
{ _geoAttenuation :: GarbageAttenuationOpts
_geoAttenuation = GarbageAttenuationOpts
defAttenuationOpts,
_geoItem :: CategoricalProbability
_geoItem = NonEmpty Double -> CategoricalProbability
CPDiscrete [Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
1],
_geoPrimary :: CategoricalProbability
_geoPrimary = NonEmpty Double -> CategoricalProbability
CPDiscrete [Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
4, Double
Item (NonEmpty Double)
4, Double
Item (NonEmpty Double)
4, Double
Item (NonEmpty Double)
4, Double
Item (NonEmpty Double)
4, Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
4, Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
1],
_geoUnary :: CategoricalProbability
_geoUnary = CategoricalProbability
uniformCP,
_geoBinary :: CategoricalProbability
_geoBinary = CategoricalProbability
uniformCP,
_geoMinTypMax :: Double
_geoMinTypMax = Double
0.5,
_geoDimRange :: Double
_geoDimRange = Double
0.5,
_geoRange :: CategoricalProbability
_geoRange = CategoricalProbability
uniformCP,
_geoRangeOffsetPos_Neg :: Double
_geoRangeOffsetPos_Neg = Double
0.5,
_geoConcatenations :: NumberProbability
_geoConcatenations = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_geoSysFunArgs :: NumberProbability
_geoSysFunArgs = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 (Double
2.0 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5.0) Int
1,
_geoLiteralWidth :: CategoricalProbability
_geoLiteralWidth =
[(Double, Int)] -> Double -> CategoricalProbability
CPBiasedUniform
[(Double
1024, Int
1), (Double
512, Int
8), (Double
256, Int
16), (Double
128, Int
32), (Double
64, Int
64), (Double
32, Int
128), (Double
16, Int
256), (Double
8, Int
512)]
Double
1,
_geoLiteralSigned :: Double
_geoLiteralSigned = Double
0.5,
_geoStringCharacters :: NumberProbability
_geoStringCharacters = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_geoStringCharacter :: CategoricalProbability
_geoStringCharacter = CategoricalProbability
uniformCP,
_geoFixed_Floating :: Double
_geoFixed_Floating = Double
0.5,
_geoExponentSign :: CategoricalProbability
_geoExponentSign = CategoricalProbability
uniformCP,
_geoX_Z :: Double
_geoX_Z = Double
0.5,
_geoBinarySymbols :: NumberProbability
_geoBinarySymbols = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_geoBinarySymbol :: CategoricalProbability
_geoBinarySymbol = CategoricalProbability
uniformCP,
_geoOctalSymbols :: NumberProbability
_geoOctalSymbols = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_geoOctalSymbol :: CategoricalProbability
_geoOctalSymbol = CategoricalProbability
uniformCP,
_geoDecimalSymbols :: NumberProbability
_geoDecimalSymbols = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_geoDecimalSymbol :: CategoricalProbability
_geoDecimalSymbol = CategoricalProbability
uniformCP,
_geoHexadecimalSymbols :: NumberProbability
_geoHexadecimalSymbols = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_geoHexadecimalSymbol :: CategoricalProbability
_geoHexadecimalSymbol = CategoricalProbability
uniformCP
},
_goIdentifier :: GarbageIdentifierOpts
_goIdentifier = GarbageIdentifierOpts
{ _gioEscaped_Simple :: Double
_gioEscaped_Simple = Double
0.5,
_gioSimpleLetters :: NumberProbability
_gioSimpleLetters = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_gioSimpleLetter :: CategoricalProbability
_gioSimpleLetter = CategoricalProbability
uniformCP,
_gioEscapedLetters :: NumberProbability
_gioEscapedLetters = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_gioEscapedLetter :: CategoricalProbability
_gioEscapedLetter = CategoricalProbability
uniformCP,
_gioSystemLetters :: NumberProbability
_gioSystemLetters = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
3,
_gioSystemFirstLetter :: CategoricalProbability
_gioSystemFirstLetter = CategoricalProbability
uniformCP
},
_goDriveStrength :: CategoricalProbability
_goDriveStrength = CategoricalProbability
uniformCP,
_goLValues :: NumberProbability
_goLValues = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.5 Int
1,
_goOptionalLValue :: Double
_goOptionalLValue = Double
0.5,
_goAttributes :: NumberProbability
_goAttributes = NonEmpty (Double, NumberProbability) -> NumberProbability
NPLinearComb [(Double
2, NonEmpty (Double, Int) -> NumberProbability
NPDiscrete [(Double
1, Int
0)]), (Double
1, Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.75 Int
1)],
_goAttributeOptionalValue :: Double
_goAttributeOptionalValue = Double
0.5,
_goDelay :: CategoricalProbability
_goDelay = NonEmpty Double -> CategoricalProbability
CPDiscrete [Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
1, Double
Item (NonEmpty Double)
2, Double
Item (NonEmpty Double)
4],
_goIntRealIdent :: CategoricalProbability
_goIntRealIdent = CategoricalProbability
uniformCP,
_goPathDepth :: NumberProbability
_goPathDepth = Int -> Double -> Int -> NumberProbability
NPNegativeBinomial Int
0 Double
0.75 Int
1,
_goBareMinTypMax :: Double
_goBareMinTypMax = Double
0.5
}
data Info = Info
{
Info -> Text
_infoCommit :: !Text,
Info -> Text
_infoVersion :: !Text
}
deriving (Info -> Info -> Bool
(Info -> Info -> Bool) -> (Info -> Info -> Bool) -> Eq Info
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Info -> Info -> Bool
== :: Info -> Info -> Bool
$c/= :: Info -> Info -> Bool
/= :: Info -> Info -> Bool
Eq, Int -> Info -> ShowS
[Info] -> ShowS
Info -> String
(Int -> Info -> ShowS)
-> (Info -> String) -> ([Info] -> ShowS) -> Show Info
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Info -> ShowS
showsPrec :: Int -> Info -> ShowS
$cshow :: Info -> String
show :: Info -> String
$cshowList :: [Info] -> ShowS
showList :: [Info] -> ShowS
Show)
data SimDescription = SimDescription {SimDescription -> Text
simName :: {-# UNPACK #-} !Text}
deriving (SimDescription -> SimDescription -> Bool
(SimDescription -> SimDescription -> Bool)
-> (SimDescription -> SimDescription -> Bool) -> Eq SimDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SimDescription -> SimDescription -> Bool
== :: SimDescription -> SimDescription -> Bool
$c/= :: SimDescription -> SimDescription -> Bool
/= :: SimDescription -> SimDescription -> Bool
Eq, Int -> SimDescription -> ShowS
[SimDescription] -> ShowS
SimDescription -> String
(Int -> SimDescription -> ShowS)
-> (SimDescription -> String)
-> ([SimDescription] -> ShowS)
-> Show SimDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SimDescription -> ShowS
showsPrec :: Int -> SimDescription -> ShowS
$cshow :: SimDescription -> String
show :: SimDescription -> String
$cshowList :: [SimDescription] -> ShowS
showList :: [SimDescription] -> ShowS
Show)
data SynthDescription = SynthDescription
{
SynthDescription -> Text
synthName :: {-# UNPACK #-} !Text,
SynthDescription -> Maybe Text
synthBin :: Maybe Text,
SynthDescription -> Maybe Text
synthDesc :: Maybe Text,
SynthDescription -> Maybe Text
synthOut :: Maybe Text
}
deriving (SynthDescription -> SynthDescription -> Bool
(SynthDescription -> SynthDescription -> Bool)
-> (SynthDescription -> SynthDescription -> Bool)
-> Eq SynthDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SynthDescription -> SynthDescription -> Bool
== :: SynthDescription -> SynthDescription -> Bool
$c/= :: SynthDescription -> SynthDescription -> Bool
/= :: SynthDescription -> SynthDescription -> Bool
Eq, Int -> SynthDescription -> ShowS
[SynthDescription] -> ShowS
SynthDescription -> String
(Int -> SynthDescription -> ShowS)
-> (SynthDescription -> String)
-> ([SynthDescription] -> ShowS)
-> Show SynthDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SynthDescription -> ShowS
showsPrec :: Int -> SynthDescription -> ShowS
$cshow :: SynthDescription -> String
show :: SynthDescription -> String
$cshowList :: [SynthDescription] -> ShowS
showList :: [SynthDescription] -> ShowS
Show)
data Config = Config
{ Config -> ConfEMI
_configEMI :: {-# UNPACK #-} !ConfEMI,
Config -> Info
_configInfo :: {-# UNPACK #-} !Info,
Config -> Probability
_configProbability :: {-# UNPACK #-} !Probability,
Config -> ConfProperty
_configProperty :: {-# UNPACK #-} !ConfProperty,
Config -> GarbageOpts
_configGarbageGenerator :: {-# UNPACK #-} !GarbageOpts,
Config -> [SimDescription]
_configSimulators :: [SimDescription],
Config -> [SynthDescription]
_configSynthesisers :: [SynthDescription]
}
deriving (Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
/= :: Config -> Config -> Bool
Eq, Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
(Int -> Config -> ShowS)
-> (Config -> String) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Config -> ShowS
showsPrec :: Int -> Config -> ShowS
$cshow :: Config -> String
show :: Config -> String
$cshowList :: [Config] -> ShowS
showList :: [Config] -> ShowS
Show)
$(makeLenses ''ProbExpr)
$(makeLenses ''ProbModItem)
$(makeLenses ''ProbStatement)
$(makeLenses ''ProbMod)
$(makeLenses ''Probability)
$(makeLenses ''ConfEMI)
$(makeLenses ''ConfProperty)
$(makeLenses ''GarbageOpts)
$(makeLenses ''GarbageConfigOpts)
$(makeLenses ''GarbagePrimitiveOpts)
$
$(makeLenses ''GarbageSpecifyOpts)
$(makeLenses ''GarbageSpecifyPathOpts)
$(makeLenses ''GarbageSpecifyTimingCheckOpts)
$(makeLenses ''GarbageGenerateOpts)
$(makeLenses ''GarbageTypeOpts)
$(makeLenses ''GarbageAttenuationOpts)
$
$(makeLenses ''GarbageExprOpts)
$(makeLenses ''GarbageIdentifierOpts)
$(makeLenses ''Info)
$(makeLenses ''Config)
$(makePrisms ''CategoricalProbability)
$(makePrisms ''NumberProbability)
defaultValue :: a -> TomlCodec a -> TomlCodec a
defaultValue :: forall a. a -> TomlCodec a -> TomlCodec a
defaultValue a
x = (a -> Maybe a)
-> (Maybe a -> a) -> TomlCodec (Maybe a) -> TomlCodec a
forall b a. (b -> a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimap a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
x) (TomlCodec (Maybe a) -> TomlCodec a)
-> (TomlCodec a -> TomlCodec (Maybe a))
-> TomlCodec a
-> TomlCodec a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlCodec a -> TomlCodec (Maybe a)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional
fromXST :: XST -> SynthDescription
fromXST :: XST -> SynthDescription
fromXST (XST Maybe String
a Text
b String
c) =
Text -> Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription
SynthDescription Text
"xst" (String -> Text
toTextIgnore (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
a) (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
b) (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
toTextIgnore String
c)
fromYosys :: Yosys -> SynthDescription
fromYosys :: Yosys -> SynthDescription
fromYosys (Yosys Maybe String
a Text
b String
c) =
Text -> Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription
SynthDescription
Text
"yosys"
(String -> Text
toTextIgnore (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
a)
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
b)
(Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
toTextIgnore String
c)
fromVivado :: Vivado -> SynthDescription
fromVivado :: Vivado -> SynthDescription
fromVivado (Vivado Maybe String
a Text
b String
c) =
Text -> Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription
SynthDescription
Text
"vivado"
(String -> Text
toTextIgnore (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
a)
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
b)
(Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
toTextIgnore String
c)
fromQuartus :: Quartus -> SynthDescription
fromQuartus :: Quartus -> SynthDescription
fromQuartus (Quartus Maybe String
a Text
b String
c) =
Text -> Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription
SynthDescription
Text
"quartus"
(String -> Text
toTextIgnore (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
a)
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
b)
(Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
toTextIgnore String
c)
fromQuartusLight :: QuartusLight -> SynthDescription
fromQuartusLight :: QuartusLight -> SynthDescription
fromQuartusLight (QuartusLight Maybe String
a Text
b String
c) =
Text -> Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription
SynthDescription
Text
"quartuslight"
(String -> Text
toTextIgnore (String -> Text) -> Maybe String -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
a)
(Text -> Maybe Text
forall a. a -> Maybe a
Just Text
b)
(Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
toTextIgnore String
c)
defaultConfig :: Config
defaultConfig :: Config
defaultConfig =
ConfEMI
-> Info
-> Probability
-> ConfProperty
-> GarbageOpts
-> [SimDescription]
-> [SynthDescription]
-> Config
Config
(Int -> Int -> ConfEMI
ConfEMI Int
2 Int
8)
(Text -> Text -> Info
Info (String -> Text
pack $(gitHash)) (String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Version -> String
showVersion Version
version))
(ProbModItem -> ProbStatement -> ProbExpr -> ProbMod -> Probability
Probability ProbModItem
defModItem ProbStatement
defStmnt ProbExpr
defExpr ProbMod
defMod)
(Int
-> Maybe Seed
-> Int
-> Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty
ConfProperty Int
20 Maybe Seed
forall a. Maybe a
Nothing Int
3 Int
2 Int
5 Text
"random" Int
10 Bool
False Int
0 Int
1 Maybe Text
forall a. Maybe a
Nothing)
GarbageOpts
defGarbageOpts
[]
[Yosys -> SynthDescription
fromYosys Yosys
defaultYosys, Vivado -> SynthDescription
fromVivado Vivado
defaultVivado]
where
defMod :: ProbMod
defMod =
Int -> Int -> ProbMod
ProbMod
Int
0
Int
1
defModItem :: ProbModItem
defModItem =
Int -> Int -> Int -> Int -> ProbModItem
ProbModItem
Int
5
Int
1
Int
1
Int
1
defStmnt :: ProbStatement
defStmnt =
Int -> Int -> Int -> Int -> ProbStatement
ProbStatement
Int
0
Int
3
Int
1
Int
0
defExpr :: ProbExpr
defExpr =
Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> ProbExpr
ProbExpr
Int
1
Int
5
Int
5
Int
5
Int
5
Int
5
Int
3
Int
0
Int
5
Int
5
twoKey :: Toml.Piece -> Toml.Piece -> Toml.Key
twoKey :: Piece -> Piece -> Key
twoKey Piece
a Piece
b = NonEmpty Piece -> Key
Toml.Key (Piece
a Piece -> [Piece] -> NonEmpty Piece
forall a. a -> [a] -> NonEmpty a
:| [Item [Piece]
Piece
b])
int :: Toml.Piece -> Toml.Piece -> TomlCodec Int
int :: Piece -> Piece -> TomlCodec Int
int Piece
a = Key -> TomlCodec Int
Toml.int (Key -> TomlCodec Int) -> (Piece -> Key) -> Piece -> TomlCodec Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Piece -> Piece -> Key
twoKey Piece
a
catProbCodec :: TomlCodec CategoricalProbability
catProbCodec :: TomlCodec CategoricalProbability
catProbCodec =
(CategoricalProbability -> Maybe (NonEmpty Double))
-> (NonEmpty Double -> CategoricalProbability)
-> TomlCodec (NonEmpty Double)
-> TomlCodec CategoricalProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch (Getting
(Leftmost (NonEmpty Double))
CategoricalProbability
(NonEmpty Double)
-> CategoricalProbability -> Maybe (NonEmpty Double)
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting
(Leftmost (NonEmpty Double))
CategoricalProbability
(NonEmpty Double)
Prism' CategoricalProbability (NonEmpty Double)
_CPDiscrete) NonEmpty Double -> CategoricalProbability
CPDiscrete (TomlBiMap Double AnyValue -> Key -> TomlCodec (NonEmpty Double)
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec (NonEmpty a)
Toml.arrayNonEmptyOf TomlBiMap Double AnyValue
Toml._Double Key
"Discrete")
TomlCodec CategoricalProbability
-> TomlCodec CategoricalProbability
-> TomlCodec CategoricalProbability
forall a.
Codec CategoricalProbability a
-> Codec CategoricalProbability a -> Codec CategoricalProbability a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TomlCodec CategoricalProbability
-> Key -> TomlCodec CategoricalProbability
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table
( ([(Double, Int)] -> Double -> CategoricalProbability)
-> Codec CategoricalProbability [(Double, Int)]
-> Codec CategoricalProbability Double
-> TomlCodec CategoricalProbability
forall a b c.
(a -> b -> c)
-> Codec CategoricalProbability a
-> Codec CategoricalProbability b
-> Codec CategoricalProbability c
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2
[(Double, Int)] -> Double -> CategoricalProbability
CPBiasedUniform
( [(Double, Int)]
-> TomlCodec [(Double, Int)] -> TomlCodec [(Double, Int)]
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue [] (TomlCodec (Double, Int) -> Key -> TomlCodec [(Double, Int)]
forall a. TomlCodec a -> Key -> TomlCodec [a]
Toml.list (TomlCodec Double -> TomlCodec Int -> TomlCodec (Double, Int)
forall a b. TomlCodec a -> TomlCodec b -> TomlCodec (a, b)
Toml.pair (Key -> TomlCodec Double
Toml.double Key
"weight") (Key -> TomlCodec Int
Toml.int Key
"value")) Key
"biases")
TomlCodec [(Double, Int)]
-> (CategoricalProbability -> [(Double, Int)])
-> Codec CategoricalProbability [(Double, Int)]
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= CategoricalProbability -> [(Double, Int)]
_CPBUBiases
)
(Key -> TomlCodec Double
Toml.double Key
"weight" TomlCodec Double
-> (CategoricalProbability -> Double)
-> Codec CategoricalProbability Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= CategoricalProbability -> Double
_CPBUUniformWeight)
)
Key
"BiasedUniform"
numProbCodec :: TomlCodec NumberProbability
numProbCodec :: TomlCodec NumberProbability
numProbCodec =
(NumberProbability -> Maybe (Int, Int))
-> ((Int, Int) -> NumberProbability)
-> TomlCodec (Int, Int)
-> TomlCodec NumberProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch
(Getting (Leftmost (Int, Int)) NumberProbability (Int, Int)
-> NumberProbability -> Maybe (Int, Int)
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting (Leftmost (Int, Int)) NumberProbability (Int, Int)
Prism' NumberProbability (Int, Int)
_NPUniform)
((Int -> Int -> NumberProbability)
-> (Int, Int) -> NumberProbability
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Int -> NumberProbability
NPUniform)
(TomlCodec (Int, Int) -> Key -> TomlCodec (Int, Int)
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table (TomlCodec Int -> TomlCodec Int -> TomlCodec (Int, Int)
forall a b. TomlCodec a -> TomlCodec b -> TomlCodec (a, b)
Toml.pair (Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue Int
0 (TomlCodec Int -> TomlCodec Int) -> TomlCodec Int -> TomlCodec Int
forall a b. (a -> b) -> a -> b
$ Key -> TomlCodec Int
Toml.int Key
"low") (Key -> TomlCodec Int
Toml.int Key
"high")) Key
"Uniform")
TomlCodec NumberProbability
-> TomlCodec NumberProbability -> TomlCodec NumberProbability
forall a.
Codec NumberProbability a
-> Codec NumberProbability a -> Codec NumberProbability a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (NumberProbability -> Maybe (Int, Int, Double))
-> ((Int, Int, Double) -> NumberProbability)
-> TomlCodec (Int, Int, Double)
-> TomlCodec NumberProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch
(Getting
(Leftmost (Int, Int, Double)) NumberProbability (Int, Int, Double)
-> NumberProbability -> Maybe (Int, Int, Double)
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting
(Leftmost (Int, Int, Double)) NumberProbability (Int, Int, Double)
Prism' NumberProbability (Int, Int, Double)
_NPBinomial)
((Int -> Int -> Double -> NumberProbability)
-> (Int, Int, Double) -> NumberProbability
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 Int -> Int -> Double -> NumberProbability
NPBinomial)
( TomlCodec (Int, Int, Double) -> Key -> TomlCodec (Int, Int, Double)
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table
( TomlCodec Int
-> TomlCodec Int
-> TomlCodec Double
-> TomlCodec (Int, Int, Double)
forall a b c.
TomlCodec a -> TomlCodec b -> TomlCodec c -> TomlCodec (a, b, c)
Toml.triple
(Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue Int
0 (Key -> TomlCodec Int
Toml.int Key
"offset"))
(Key -> TomlCodec Int
Toml.int Key
"trials")
(Key -> TomlCodec Double
Toml.double Key
"succesRate")
)
Key
"Binomial"
)
TomlCodec NumberProbability
-> TomlCodec NumberProbability -> TomlCodec NumberProbability
forall a.
Codec NumberProbability a
-> Codec NumberProbability a -> Codec NumberProbability a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (NumberProbability -> Maybe (Int, Double, Int))
-> ((Int, Double, Int) -> NumberProbability)
-> TomlCodec (Int, Double, Int)
-> TomlCodec NumberProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch
(Getting
(Leftmost (Int, Double, Int)) NumberProbability (Int, Double, Int)
-> NumberProbability -> Maybe (Int, Double, Int)
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting
(Leftmost (Int, Double, Int)) NumberProbability (Int, Double, Int)
Prism' NumberProbability (Int, Double, Int)
_NPNegativeBinomial)
((Int -> Double -> Int -> NumberProbability)
-> (Int, Double, Int) -> NumberProbability
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 Int -> Double -> Int -> NumberProbability
NPNegativeBinomial)
( TomlCodec (Int, Double, Int) -> Key -> TomlCodec (Int, Double, Int)
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table
( TomlCodec Int
-> TomlCodec Double
-> TomlCodec Int
-> TomlCodec (Int, Double, Int)
forall a b c.
TomlCodec a -> TomlCodec b -> TomlCodec c -> TomlCodec (a, b, c)
Toml.triple
(Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue Int
0 (Key -> TomlCodec Int
Toml.int Key
"offset"))
(Key -> TomlCodec Double
Toml.double Key
"failureRate")
(Key -> TomlCodec Int
Toml.int Key
"numberOfFailures")
)
Key
"NegativeBinomial"
)
TomlCodec NumberProbability
-> TomlCodec NumberProbability -> TomlCodec NumberProbability
forall a.
Codec NumberProbability a
-> Codec NumberProbability a -> Codec NumberProbability a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (NumberProbability -> Maybe (Int, Double, Int))
-> ((Int, Double, Int) -> NumberProbability)
-> TomlCodec (Int, Double, Int)
-> TomlCodec NumberProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch
(Getting
(Leftmost (Int, Double, Int)) NumberProbability (Int, Double, Int)
-> NumberProbability -> Maybe (Int, Double, Int)
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting
(Leftmost (Int, Double, Int)) NumberProbability (Int, Double, Int)
Prism' NumberProbability (Int, Double, Int)
_NPNegativeBinomial)
((Int -> Double -> Int -> NumberProbability)
-> (Int, Double, Int) -> NumberProbability
forall a b c d. (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 Int -> Double -> Int -> NumberProbability
NPNegativeBinomial)
( TomlCodec (Int, Double, Int) -> Key -> TomlCodec (Int, Double, Int)
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table
( TomlCodec Int
-> TomlCodec Double
-> TomlCodec Int
-> TomlCodec (Int, Double, Int)
forall a b c.
TomlCodec a -> TomlCodec b -> TomlCodec c -> TomlCodec (a, b, c)
Toml.triple
(Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue Int
0 (Key -> TomlCodec Int
Toml.int Key
"offset"))
(Key -> TomlCodec Double
Toml.double Key
"failureRate")
(Int -> TomlCodec Int
forall a. a -> Codec Int a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
1)
)
Key
"Geometric"
)
TomlCodec NumberProbability
-> TomlCodec NumberProbability -> TomlCodec NumberProbability
forall a.
Codec NumberProbability a
-> Codec NumberProbability a -> Codec NumberProbability a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (NumberProbability -> Maybe (Int, Double))
-> ((Int, Double) -> NumberProbability)
-> TomlCodec (Int, Double)
-> TomlCodec NumberProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch
(Getting (Leftmost (Int, Double)) NumberProbability (Int, Double)
-> NumberProbability -> Maybe (Int, Double)
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting (Leftmost (Int, Double)) NumberProbability (Int, Double)
Prism' NumberProbability (Int, Double)
_NPPoisson)
((Int -> Double -> NumberProbability)
-> (Int, Double) -> NumberProbability
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Int -> Double -> NumberProbability
NPPoisson)
(TomlCodec (Int, Double) -> Key -> TomlCodec (Int, Double)
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table (TomlCodec Int -> TomlCodec Double -> TomlCodec (Int, Double)
forall a b. TomlCodec a -> TomlCodec b -> TomlCodec (a, b)
Toml.pair (Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue Int
0 (Key -> TomlCodec Int
Toml.int Key
"offset")) (Key -> TomlCodec Double
Toml.double Key
"lambda")) Key
"Poisson")
TomlCodec NumberProbability
-> TomlCodec NumberProbability -> TomlCodec NumberProbability
forall a.
Codec NumberProbability a
-> Codec NumberProbability a -> Codec NumberProbability a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (NumberProbability -> Maybe (NonEmpty (Double, Int)))
-> (NonEmpty (Double, Int) -> NumberProbability)
-> TomlCodec (NonEmpty (Double, Int))
-> TomlCodec NumberProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch
(Getting
(Leftmost (NonEmpty (Double, Int)))
NumberProbability
(NonEmpty (Double, Int))
-> NumberProbability -> Maybe (NonEmpty (Double, Int))
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting
(Leftmost (NonEmpty (Double, Int)))
NumberProbability
(NonEmpty (Double, Int))
Prism' NumberProbability (NonEmpty (Double, Int))
_NPDiscrete)
NonEmpty (Double, Int) -> NumberProbability
NPDiscrete
(TomlCodec (Double, Int)
-> Key -> TomlCodec (NonEmpty (Double, Int))
forall a. TomlCodec a -> Key -> TomlCodec (NonEmpty a)
Toml.nonEmpty (TomlCodec Double -> TomlCodec Int -> TomlCodec (Double, Int)
forall a b. TomlCodec a -> TomlCodec b -> TomlCodec (a, b)
Toml.pair (Key -> TomlCodec Double
Toml.double Key
"weight") (Key -> TomlCodec Int
Toml.int Key
"value")) Key
"Discrete")
TomlCodec NumberProbability
-> TomlCodec NumberProbability -> TomlCodec NumberProbability
forall a.
Codec NumberProbability a
-> Codec NumberProbability a -> Codec NumberProbability a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (NumberProbability -> Maybe (NonEmpty (Double, NumberProbability)))
-> (NonEmpty (Double, NumberProbability) -> NumberProbability)
-> TomlCodec (NonEmpty (Double, NumberProbability))
-> TomlCodec NumberProbability
forall b a.
(b -> Maybe a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimatch
(Getting
(Leftmost (NonEmpty (Double, NumberProbability)))
NumberProbability
(NonEmpty (Double, NumberProbability))
-> NumberProbability
-> Maybe (NonEmpty (Double, NumberProbability))
forall a s. Getting (Leftmost a) s a -> s -> Maybe a
firstOf Getting
(Leftmost (NonEmpty (Double, NumberProbability)))
NumberProbability
(NonEmpty (Double, NumberProbability))
Prism' NumberProbability (NonEmpty (Double, NumberProbability))
_NPLinearComb)
NonEmpty (Double, NumberProbability) -> NumberProbability
NPLinearComb
(TomlCodec (Double, NumberProbability)
-> Key -> TomlCodec (NonEmpty (Double, NumberProbability))
forall a. TomlCodec a -> Key -> TomlCodec (NonEmpty a)
Toml.nonEmpty (TomlCodec Double
-> TomlCodec NumberProbability
-> TomlCodec (Double, NumberProbability)
forall a b. TomlCodec a -> TomlCodec b -> TomlCodec (a, b)
Toml.pair (Key -> TomlCodec Double
Toml.double Key
"weight") TomlCodec NumberProbability
numProbCodec) Key
"LinearCombination")
exprCodec :: TomlCodec ProbExpr
exprCodec :: TomlCodec ProbExpr
exprCodec =
Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> ProbExpr
ProbExpr
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> ProbExpr)
-> Codec ProbExpr Int
-> Codec
ProbExpr
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> ProbExpr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprNum) (Piece -> TomlCodec Int
intE Piece
"number")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprNum
Codec
ProbExpr
(Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> Int
-> ProbExpr)
-> Codec ProbExpr Int
-> Codec
ProbExpr
(Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprId) (Piece -> TomlCodec Int
intE Piece
"variable")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprId
Codec
ProbExpr
(Int -> Int -> Int -> Int -> Int -> Int -> Int -> Int -> ProbExpr)
-> Codec ProbExpr Int
-> Codec
ProbExpr
(Int -> Int -> Int -> Int -> Int -> Int -> Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprRangeSelect) (Piece -> TomlCodec Int
intE Piece
"rangeselect")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprRangeSelect
Codec
ProbExpr
(Int -> Int -> Int -> Int -> Int -> Int -> Int -> ProbExpr)
-> Codec ProbExpr Int
-> Codec
ProbExpr (Int -> Int -> Int -> Int -> Int -> Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprUnOp) (Piece -> TomlCodec Int
intE Piece
"unary")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprUnOp
Codec ProbExpr (Int -> Int -> Int -> Int -> Int -> Int -> ProbExpr)
-> Codec ProbExpr Int
-> Codec ProbExpr (Int -> Int -> Int -> Int -> Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprBinOp) (Piece -> TomlCodec Int
intE Piece
"binary")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprBinOp
Codec ProbExpr (Int -> Int -> Int -> Int -> Int -> ProbExpr)
-> Codec ProbExpr Int
-> Codec ProbExpr (Int -> Int -> Int -> Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprCond) (Piece -> TomlCodec Int
intE Piece
"ternary")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprCond
Codec ProbExpr (Int -> Int -> Int -> Int -> ProbExpr)
-> Codec ProbExpr Int
-> Codec ProbExpr (Int -> Int -> Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprConcat) (Piece -> TomlCodec Int
intE Piece
"concatenation")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprConcat
Codec ProbExpr (Int -> Int -> Int -> ProbExpr)
-> Codec ProbExpr Int -> Codec ProbExpr (Int -> Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprStr) (Piece -> TomlCodec Int
intE Piece
"string")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprStr
Codec ProbExpr (Int -> Int -> ProbExpr)
-> Codec ProbExpr Int -> Codec ProbExpr (Int -> ProbExpr)
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprSigned) (Piece -> TomlCodec Int
intE Piece
"signed")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprSigned
Codec ProbExpr (Int -> ProbExpr)
-> Codec ProbExpr Int -> TomlCodec ProbExpr
forall a b.
Codec ProbExpr (a -> b) -> Codec ProbExpr a -> Codec ProbExpr b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr) -> Int
forall {a}. ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (Int -> Const Int Int) -> ProbExpr -> Const Int ProbExpr
Lens' ProbExpr Int
probExprUnsigned) (Piece -> TomlCodec Int
intE Piece
"unsigned")
TomlCodec Int -> (ProbExpr -> Int) -> Codec ProbExpr Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbExpr -> Int
_probExprUnsigned
where
defProb :: ((a -> Const a a) -> ProbExpr -> Const a ProbExpr) -> a
defProb (a -> Const a a) -> ProbExpr -> Const a ProbExpr
i = Config
defaultConfig Config -> Getting a Config a -> a
forall s a. s -> Getting a s a -> a
^. (Probability -> Const a Probability) -> Config -> Const a Config
Lens' Config Probability
configProbability ((Probability -> Const a Probability) -> Config -> Const a Config)
-> ((a -> Const a a) -> Probability -> Const a Probability)
-> Getting a Config a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProbExpr -> Const a ProbExpr)
-> Probability -> Const a Probability
Lens' Probability ProbExpr
probExpr ((ProbExpr -> Const a ProbExpr)
-> Probability -> Const a Probability)
-> ((a -> Const a a) -> ProbExpr -> Const a ProbExpr)
-> (a -> Const a a)
-> Probability
-> Const a Probability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const a a) -> ProbExpr -> Const a ProbExpr
i
intE :: Piece -> TomlCodec Int
intE = Piece -> Piece -> TomlCodec Int
int Piece
"expr"
stmntCodec :: TomlCodec ProbStatement
stmntCodec :: TomlCodec ProbStatement
stmntCodec =
Int -> Int -> Int -> Int -> ProbStatement
ProbStatement
(Int -> Int -> Int -> Int -> ProbStatement)
-> Codec ProbStatement Int
-> Codec ProbStatement (Int -> Int -> Int -> ProbStatement)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int)
-> ProbStatement -> Const Int ProbStatement)
-> Int
forall {a}.
((a -> Const a a) -> ProbStatement -> Const a ProbStatement) -> a
defProb (Int -> Const Int Int) -> ProbStatement -> Const Int ProbStatement
Lens' ProbStatement Int
probStmntBlock) (Piece -> TomlCodec Int
intS Piece
"blocking")
TomlCodec Int -> (ProbStatement -> Int) -> Codec ProbStatement Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbStatement -> Int
_probStmntBlock
Codec ProbStatement (Int -> Int -> Int -> ProbStatement)
-> Codec ProbStatement Int
-> Codec ProbStatement (Int -> Int -> ProbStatement)
forall a b.
Codec ProbStatement (a -> b)
-> Codec ProbStatement a -> Codec ProbStatement b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int)
-> ProbStatement -> Const Int ProbStatement)
-> Int
forall {a}.
((a -> Const a a) -> ProbStatement -> Const a ProbStatement) -> a
defProb (Int -> Const Int Int) -> ProbStatement -> Const Int ProbStatement
Lens' ProbStatement Int
probStmntNonBlock) (Piece -> TomlCodec Int
intS Piece
"nonblocking")
TomlCodec Int -> (ProbStatement -> Int) -> Codec ProbStatement Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbStatement -> Int
_probStmntNonBlock
Codec ProbStatement (Int -> Int -> ProbStatement)
-> Codec ProbStatement Int
-> Codec ProbStatement (Int -> ProbStatement)
forall a b.
Codec ProbStatement (a -> b)
-> Codec ProbStatement a -> Codec ProbStatement b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int)
-> ProbStatement -> Const Int ProbStatement)
-> Int
forall {a}.
((a -> Const a a) -> ProbStatement -> Const a ProbStatement) -> a
defProb (Int -> Const Int Int) -> ProbStatement -> Const Int ProbStatement
Lens' ProbStatement Int
probStmntCond) (Piece -> TomlCodec Int
intS Piece
"conditional")
TomlCodec Int -> (ProbStatement -> Int) -> Codec ProbStatement Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbStatement -> Int
_probStmntCond
Codec ProbStatement (Int -> ProbStatement)
-> Codec ProbStatement Int -> TomlCodec ProbStatement
forall a b.
Codec ProbStatement (a -> b)
-> Codec ProbStatement a -> Codec ProbStatement b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int)
-> ProbStatement -> Const Int ProbStatement)
-> Int
forall {a}.
((a -> Const a a) -> ProbStatement -> Const a ProbStatement) -> a
defProb (Int -> Const Int Int) -> ProbStatement -> Const Int ProbStatement
Lens' ProbStatement Int
probStmntFor) (Piece -> TomlCodec Int
intS Piece
"forloop")
TomlCodec Int -> (ProbStatement -> Int) -> Codec ProbStatement Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbStatement -> Int
_probStmntFor
where
defProb :: ((a -> Const a a) -> ProbStatement -> Const a ProbStatement) -> a
defProb (a -> Const a a) -> ProbStatement -> Const a ProbStatement
i = Config
defaultConfig Config -> Getting a Config a -> a
forall s a. s -> Getting a s a -> a
^. (Probability -> Const a Probability) -> Config -> Const a Config
Lens' Config Probability
configProbability ((Probability -> Const a Probability) -> Config -> Const a Config)
-> ((a -> Const a a) -> Probability -> Const a Probability)
-> Getting a Config a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProbStatement -> Const a ProbStatement)
-> Probability -> Const a Probability
Lens' Probability ProbStatement
probStmnt ((ProbStatement -> Const a ProbStatement)
-> Probability -> Const a Probability)
-> ((a -> Const a a) -> ProbStatement -> Const a ProbStatement)
-> (a -> Const a a)
-> Probability
-> Const a Probability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const a a) -> ProbStatement -> Const a ProbStatement
i
intS :: Piece -> TomlCodec Int
intS = Piece -> Piece -> TomlCodec Int
int Piece
"statement"
modItemCodec :: TomlCodec ProbModItem
modItemCodec :: TomlCodec ProbModItem
modItemCodec =
Int -> Int -> Int -> Int -> ProbModItem
ProbModItem
(Int -> Int -> Int -> Int -> ProbModItem)
-> Codec ProbModItem Int
-> Codec ProbModItem (Int -> Int -> Int -> ProbModItem)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem)
-> Int
forall {a}.
((a -> Const a a) -> ProbModItem -> Const a ProbModItem) -> a
defProb (Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem
Lens' ProbModItem Int
probModItemAssign) (Piece -> TomlCodec Int
intM Piece
"assign")
TomlCodec Int -> (ProbModItem -> Int) -> Codec ProbModItem Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbModItem -> Int
_probModItemAssign
Codec ProbModItem (Int -> Int -> Int -> ProbModItem)
-> Codec ProbModItem Int
-> Codec ProbModItem (Int -> Int -> ProbModItem)
forall a b.
Codec ProbModItem (a -> b)
-> Codec ProbModItem a -> Codec ProbModItem b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem)
-> Int
forall {a}.
((a -> Const a a) -> ProbModItem -> Const a ProbModItem) -> a
defProb (Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem
Lens' ProbModItem Int
probModItemSeqAlways) (Piece -> TomlCodec Int
intM Piece
"sequential")
TomlCodec Int -> (ProbModItem -> Int) -> Codec ProbModItem Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbModItem -> Int
_probModItemSeqAlways
Codec ProbModItem (Int -> Int -> ProbModItem)
-> Codec ProbModItem Int -> Codec ProbModItem (Int -> ProbModItem)
forall a b.
Codec ProbModItem (a -> b)
-> Codec ProbModItem a -> Codec ProbModItem b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem)
-> Int
forall {a}.
((a -> Const a a) -> ProbModItem -> Const a ProbModItem) -> a
defProb (Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem
Lens' ProbModItem Int
probModItemCombAlways) (Piece -> TomlCodec Int
intM Piece
"combinational")
TomlCodec Int -> (ProbModItem -> Int) -> Codec ProbModItem Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbModItem -> Int
_probModItemCombAlways
Codec ProbModItem (Int -> ProbModItem)
-> Codec ProbModItem Int -> TomlCodec ProbModItem
forall a b.
Codec ProbModItem (a -> b)
-> Codec ProbModItem a -> Codec ProbModItem b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem)
-> Int
forall {a}.
((a -> Const a a) -> ProbModItem -> Const a ProbModItem) -> a
defProb (Int -> Const Int Int) -> ProbModItem -> Const Int ProbModItem
Lens' ProbModItem Int
probModItemInst) (Piece -> TomlCodec Int
intM Piece
"instantiation")
TomlCodec Int -> (ProbModItem -> Int) -> Codec ProbModItem Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbModItem -> Int
_probModItemInst
where
defProb :: ((a -> Const a a) -> ProbModItem -> Const a ProbModItem) -> a
defProb (a -> Const a a) -> ProbModItem -> Const a ProbModItem
i = Config
defaultConfig Config -> Getting a Config a -> a
forall s a. s -> Getting a s a -> a
^. (Probability -> Const a Probability) -> Config -> Const a Config
Lens' Config Probability
configProbability ((Probability -> Const a Probability) -> Config -> Const a Config)
-> ((a -> Const a a) -> Probability -> Const a Probability)
-> Getting a Config a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProbModItem -> Const a ProbModItem)
-> Probability -> Const a Probability
Lens' Probability ProbModItem
probModItem ((ProbModItem -> Const a ProbModItem)
-> Probability -> Const a Probability)
-> ((a -> Const a a) -> ProbModItem -> Const a ProbModItem)
-> (a -> Const a a)
-> Probability
-> Const a Probability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const a a) -> ProbModItem -> Const a ProbModItem
i
intM :: Piece -> TomlCodec Int
intM = Piece -> Piece -> TomlCodec Int
int Piece
"moditem"
modCodec :: TomlCodec ProbMod
modCodec :: TomlCodec ProbMod
modCodec =
Int -> Int -> ProbMod
ProbMod
(Int -> Int -> ProbMod)
-> Codec ProbMod Int -> Codec ProbMod (Int -> ProbMod)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbMod -> Const Int ProbMod) -> Int
forall {a}. ((a -> Const a a) -> ProbMod -> Const a ProbMod) -> a
defProb (Int -> Const Int Int) -> ProbMod -> Const Int ProbMod
Lens' ProbMod Int
probModDropOutput) (Piece -> TomlCodec Int
intM Piece
"drop_output")
TomlCodec Int -> (ProbMod -> Int) -> Codec ProbMod Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbMod -> Int
_probModDropOutput
Codec ProbMod (Int -> ProbMod)
-> Codec ProbMod Int -> TomlCodec ProbMod
forall a b.
Codec ProbMod (a -> b) -> Codec ProbMod a -> Codec ProbMod b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ProbMod -> Const Int ProbMod) -> Int
forall {a}. ((a -> Const a a) -> ProbMod -> Const a ProbMod) -> a
defProb (Int -> Const Int Int) -> ProbMod -> Const Int ProbMod
Lens' ProbMod Int
probModKeepOutput) (Piece -> TomlCodec Int
intM Piece
"keep_output")
TomlCodec Int -> (ProbMod -> Int) -> Codec ProbMod Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ProbMod -> Int
_probModKeepOutput
where
defProb :: ((a -> Const a a) -> ProbMod -> Const a ProbMod) -> a
defProb (a -> Const a a) -> ProbMod -> Const a ProbMod
i = Config
defaultConfig Config -> Getting a Config a -> a
forall s a. s -> Getting a s a -> a
^. (Probability -> Const a Probability) -> Config -> Const a Config
Lens' Config Probability
configProbability ((Probability -> Const a Probability) -> Config -> Const a Config)
-> ((a -> Const a a) -> Probability -> Const a Probability)
-> Getting a Config a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProbMod -> Const a ProbMod) -> Probability -> Const a Probability
Lens' Probability ProbMod
probMod ((ProbMod -> Const a ProbMod)
-> Probability -> Const a Probability)
-> ((a -> Const a a) -> ProbMod -> Const a ProbMod)
-> (a -> Const a a)
-> Probability
-> Const a Probability
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const a a) -> ProbMod -> Const a ProbMod
i
intM :: Piece -> TomlCodec Int
intM = Piece -> Piece -> TomlCodec Int
int Piece
"module"
probCodec :: TomlCodec Probability
probCodec :: TomlCodec Probability
probCodec =
ProbModItem -> ProbStatement -> ProbExpr -> ProbMod -> Probability
Probability
(ProbModItem
-> ProbStatement -> ProbExpr -> ProbMod -> Probability)
-> Codec Probability ProbModItem
-> Codec
Probability (ProbStatement -> ProbExpr -> ProbMod -> Probability)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ProbModItem -> TomlCodec ProbModItem -> TomlCodec ProbModItem
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((ProbModItem -> Const ProbModItem ProbModItem)
-> Probability -> Const ProbModItem Probability)
-> ProbModItem
forall {a}.
((a -> Const a a) -> Probability -> Const a Probability) -> a
defProb (ProbModItem -> Const ProbModItem ProbModItem)
-> Probability -> Const ProbModItem Probability
Lens' Probability ProbModItem
probModItem) TomlCodec ProbModItem
modItemCodec
TomlCodec ProbModItem
-> (Probability -> ProbModItem) -> Codec Probability ProbModItem
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Probability -> ProbModItem
_probModItem
Codec
Probability (ProbStatement -> ProbExpr -> ProbMod -> Probability)
-> Codec Probability ProbStatement
-> Codec Probability (ProbExpr -> ProbMod -> Probability)
forall a b.
Codec Probability (a -> b)
-> Codec Probability a -> Codec Probability b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ProbStatement -> TomlCodec ProbStatement -> TomlCodec ProbStatement
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((ProbStatement -> Const ProbStatement ProbStatement)
-> Probability -> Const ProbStatement Probability)
-> ProbStatement
forall {a}.
((a -> Const a a) -> Probability -> Const a Probability) -> a
defProb (ProbStatement -> Const ProbStatement ProbStatement)
-> Probability -> Const ProbStatement Probability
Lens' Probability ProbStatement
probStmnt) TomlCodec ProbStatement
stmntCodec
TomlCodec ProbStatement
-> (Probability -> ProbStatement)
-> Codec Probability ProbStatement
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Probability -> ProbStatement
_probStmnt
Codec Probability (ProbExpr -> ProbMod -> Probability)
-> Codec Probability ProbExpr
-> Codec Probability (ProbMod -> Probability)
forall a b.
Codec Probability (a -> b)
-> Codec Probability a -> Codec Probability b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ProbExpr -> TomlCodec ProbExpr -> TomlCodec ProbExpr
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((ProbExpr -> Const ProbExpr ProbExpr)
-> Probability -> Const ProbExpr Probability)
-> ProbExpr
forall {a}.
((a -> Const a a) -> Probability -> Const a Probability) -> a
defProb (ProbExpr -> Const ProbExpr ProbExpr)
-> Probability -> Const ProbExpr Probability
Lens' Probability ProbExpr
probExpr) TomlCodec ProbExpr
exprCodec
TomlCodec ProbExpr
-> (Probability -> ProbExpr) -> Codec Probability ProbExpr
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Probability -> ProbExpr
_probExpr
Codec Probability (ProbMod -> Probability)
-> Codec Probability ProbMod -> TomlCodec Probability
forall a b.
Codec Probability (a -> b)
-> Codec Probability a -> Codec Probability b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ProbMod -> TomlCodec ProbMod -> TomlCodec ProbMod
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((ProbMod -> Const ProbMod ProbMod)
-> Probability -> Const ProbMod Probability)
-> ProbMod
forall {a}.
((a -> Const a a) -> Probability -> Const a Probability) -> a
defProb (ProbMod -> Const ProbMod ProbMod)
-> Probability -> Const ProbMod Probability
Lens' Probability ProbMod
probMod) TomlCodec ProbMod
modCodec
TomlCodec ProbMod
-> (Probability -> ProbMod) -> Codec Probability ProbMod
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Probability -> ProbMod
_probMod
where
defProb :: ((a -> Const a a) -> Probability -> Const a Probability) -> a
defProb (a -> Const a a) -> Probability -> Const a Probability
i = Config
defaultConfig Config -> Getting a Config a -> a
forall s a. s -> Getting a s a -> a
^. (Probability -> Const a Probability) -> Config -> Const a Config
Lens' Config Probability
configProbability ((Probability -> Const a Probability) -> Config -> Const a Config)
-> ((a -> Const a a) -> Probability -> Const a Probability)
-> Getting a Config a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const a a) -> Probability -> Const a Probability
i
propCodec :: TomlCodec ConfProperty
propCodec :: TomlCodec ConfProperty
propCodec =
Int
-> Maybe Seed
-> Int
-> Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty
ConfProperty
(Int
-> Maybe Seed
-> Int
-> Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty)
-> Codec ConfProperty Int
-> Codec
ConfProperty
(Maybe Seed
-> Int
-> Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty)
-> Int
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty
Lens' ConfProperty Int
propSize) (Key -> TomlCodec Int
Toml.int Key
"size")
TomlCodec Int -> (ConfProperty -> Int) -> Codec ConfProperty Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Int
_propSize
Codec
ConfProperty
(Maybe Seed
-> Int
-> Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty)
-> Codec ConfProperty (Maybe Seed)
-> Codec
ConfProperty
(Int
-> Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec Seed -> TomlCodec (Maybe Seed)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Seed
forall a. (Show a, Read a) => Key -> TomlCodec a
Toml.read Key
"seed")
TomlCodec (Maybe Seed)
-> (ConfProperty -> Maybe Seed) -> Codec ConfProperty (Maybe Seed)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Maybe Seed
_propSeed
Codec
ConfProperty
(Int
-> Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty)
-> Codec ConfProperty Int
-> Codec
ConfProperty
(Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty)
-> Int
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty
Lens' ConfProperty Int
propStmntDepth) (Piece -> Piece -> TomlCodec Int
int Piece
"statement" Piece
"depth")
TomlCodec Int -> (ConfProperty -> Int) -> Codec ConfProperty Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Int
_propStmntDepth
Codec
ConfProperty
(Int
-> Int
-> Text
-> Int
-> Bool
-> Int
-> Int
-> Maybe Text
-> ConfProperty)
-> Codec ConfProperty Int
-> Codec
ConfProperty
(Int
-> Text -> Int -> Bool -> Int -> Int -> Maybe Text -> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty)
-> Int
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty
Lens' ConfProperty Int
propModDepth) (Piece -> Piece -> TomlCodec Int
int Piece
"module" Piece
"depth")
TomlCodec Int -> (ConfProperty -> Int) -> Codec ConfProperty Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Int
_propModDepth
Codec
ConfProperty
(Int
-> Text -> Int -> Bool -> Int -> Int -> Maybe Text -> ConfProperty)
-> Codec ConfProperty Int
-> Codec
ConfProperty
(Text -> Int -> Bool -> Int -> Int -> Maybe Text -> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty)
-> Int
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty
Lens' ConfProperty Int
propMaxModules) (Piece -> Piece -> TomlCodec Int
int Piece
"module" Piece
"max")
TomlCodec Int -> (ConfProperty -> Int) -> Codec ConfProperty Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Int
_propMaxModules
Codec
ConfProperty
(Text -> Int -> Bool -> Int -> Int -> Maybe Text -> ConfProperty)
-> Codec ConfProperty Text
-> Codec
ConfProperty
(Int -> Bool -> Int -> Int -> Maybe Text -> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> TomlCodec Text -> TomlCodec Text
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(((Text -> Const Text Text)
-> ConfProperty -> Const Text ConfProperty)
-> Text
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Text -> Const Text Text)
-> ConfProperty -> Const Text ConfProperty
Lens' ConfProperty Text
propSampleMethod)
(Key -> TomlCodec Text
Toml.text (Piece -> Piece -> Key
twoKey Piece
"sample" Piece
"method"))
TomlCodec Text -> (ConfProperty -> Text) -> Codec ConfProperty Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Text
_propSampleMethod
Codec
ConfProperty
(Int -> Bool -> Int -> Int -> Maybe Text -> ConfProperty)
-> Codec ConfProperty Int
-> Codec
ConfProperty (Bool -> Int -> Int -> Maybe Text -> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty)
-> Int
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty
Lens' ConfProperty Int
propSampleSize) (Piece -> Piece -> TomlCodec Int
int Piece
"sample" Piece
"size")
TomlCodec Int -> (ConfProperty -> Int) -> Codec ConfProperty Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Int
_propSampleSize
Codec
ConfProperty (Bool -> Int -> Int -> Maybe Text -> ConfProperty)
-> Codec ConfProperty Bool
-> Codec ConfProperty (Int -> Int -> Maybe Text -> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Bool -> TomlCodec Bool -> TomlCodec Bool
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(((Bool -> Const Bool Bool)
-> ConfProperty -> Const Bool ConfProperty)
-> Bool
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Bool -> Const Bool Bool)
-> ConfProperty -> Const Bool ConfProperty
Lens' ConfProperty Bool
propCombine)
(Key -> TomlCodec Bool
Toml.bool (Piece -> Piece -> Key
twoKey Piece
"output" Piece
"combine"))
TomlCodec Bool -> (ConfProperty -> Bool) -> Codec ConfProperty Bool
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Bool
_propCombine
Codec ConfProperty (Int -> Int -> Maybe Text -> ConfProperty)
-> Codec ConfProperty Int
-> Codec ConfProperty (Int -> Maybe Text -> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty)
-> Int
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty
Lens' ConfProperty Int
propNonDeterminism) (Key -> TomlCodec Int
Toml.int Key
"nondeterminism")
TomlCodec Int -> (ConfProperty -> Int) -> Codec ConfProperty Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Int
_propNonDeterminism
Codec ConfProperty (Int -> Maybe Text -> ConfProperty)
-> Codec ConfProperty Int
-> Codec ConfProperty (Maybe Text -> ConfProperty)
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (((Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty)
-> Int
forall {a}.
((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (Int -> Const Int Int) -> ConfProperty -> Const Int ConfProperty
Lens' ConfProperty Int
propDeterminism) (Key -> TomlCodec Int
Toml.int Key
"determinism")
TomlCodec Int -> (ConfProperty -> Int) -> Codec ConfProperty Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Int
_propDeterminism
Codec ConfProperty (Maybe Text -> ConfProperty)
-> Codec ConfProperty (Maybe Text) -> TomlCodec ConfProperty
forall a b.
Codec ConfProperty (a -> b)
-> Codec ConfProperty a -> Codec ConfProperty b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec Text -> TomlCodec (Maybe Text)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Text
Toml.text (Piece -> Piece -> Key
twoKey Piece
"default" Piece
"yosys"))
TomlCodec (Maybe Text)
-> (ConfProperty -> Maybe Text) -> Codec ConfProperty (Maybe Text)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfProperty -> Maybe Text
_propDefaultYosys
where
defProp :: ((a -> Const a a) -> ConfProperty -> Const a ConfProperty) -> a
defProp (a -> Const a a) -> ConfProperty -> Const a ConfProperty
i = Config
defaultConfig Config -> Getting a Config a -> a
forall s a. s -> Getting a s a -> a
^. (ConfProperty -> Const a ConfProperty) -> Config -> Const a Config
Lens' Config ConfProperty
configProperty ((ConfProperty -> Const a ConfProperty)
-> Config -> Const a Config)
-> ((a -> Const a a) -> ConfProperty -> Const a ConfProperty)
-> Getting a Config a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Const a a) -> ConfProperty -> Const a ConfProperty
i
garbageAttenuationCodec :: Toml.Key -> TomlCodec GarbageAttenuationOpts
garbageAttenuationCodec :: Key -> TomlCodec GarbageAttenuationOpts
garbageAttenuationCodec =
(GarbageAttenuationOpts -> Double)
-> (Double -> GarbageAttenuationOpts)
-> TomlCodec Double
-> TomlCodec GarbageAttenuationOpts
forall b a. (b -> a) -> (a -> b) -> TomlCodec a -> TomlCodec b
Toml.dimap GarbageAttenuationOpts -> Double
_gaoDecrease (Double -> Double -> GarbageAttenuationOpts
GarbageAttenuationOpts Double
1.0)
(TomlCodec Double -> TomlCodec GarbageAttenuationOpts)
-> (Key -> TomlCodec Double)
-> Key
-> TomlCodec GarbageAttenuationOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageAttenuationOpts -> Double
_gaoDecrease GarbageAttenuationOpts
defAttenuationOpts)
(TomlCodec Double -> TomlCodec Double)
-> (Key -> TomlCodec Double) -> Key -> TomlCodec Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> TomlCodec Double
Toml.double
garbageConfigCodec :: TomlCodec GarbageConfigOpts
garbageConfigCodec :: TomlCodec GarbageConfigOpts
garbageConfigCodec =
NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageConfigOpts
GarbageConfigOpts
(NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageConfigOpts)
-> Codec GarbageConfigOpts NumberProbability
-> Codec
GarbageConfigOpts
(NumberProbability
-> NumberProbability
-> NumberProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageConfigOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageConfigOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageConfigOpts NumberProbability
forall {a}.
(GarbageConfigOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageConfigOpts a
tfield GarbageConfigOpts -> NumberProbability
_gcoBlocks Key
"blocks" TomlCodec NumberProbability
numProbCodec
Codec
GarbageConfigOpts
(NumberProbability
-> NumberProbability
-> NumberProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageConfigOpts)
-> Codec GarbageConfigOpts NumberProbability
-> Codec
GarbageConfigOpts
(NumberProbability
-> NumberProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageConfigOpts)
forall a b.
Codec GarbageConfigOpts (a -> b)
-> Codec GarbageConfigOpts a -> Codec GarbageConfigOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageConfigOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageConfigOpts NumberProbability
forall {a}.
(GarbageConfigOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageConfigOpts a
tfield GarbageConfigOpts -> NumberProbability
_gcoDesigns Key
"designs" TomlCodec NumberProbability
numProbCodec
Codec
GarbageConfigOpts
(NumberProbability
-> NumberProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageConfigOpts)
-> Codec GarbageConfigOpts NumberProbability
-> Codec
GarbageConfigOpts
(NumberProbability
-> Double -> Double -> Double -> Double -> GarbageConfigOpts)
forall a b.
Codec GarbageConfigOpts (a -> b)
-> Codec GarbageConfigOpts a -> Codec GarbageConfigOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageConfigOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageConfigOpts NumberProbability
forall {a}.
(GarbageConfigOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageConfigOpts a
tfield GarbageConfigOpts -> NumberProbability
_gcoItems Key
"items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageConfigOpts
(NumberProbability
-> Double -> Double -> Double -> Double -> GarbageConfigOpts)
-> Codec GarbageConfigOpts NumberProbability
-> Codec
GarbageConfigOpts
(Double -> Double -> Double -> Double -> GarbageConfigOpts)
forall a b.
Codec GarbageConfigOpts (a -> b)
-> Codec GarbageConfigOpts a -> Codec GarbageConfigOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageConfigOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageConfigOpts NumberProbability
forall {a}.
(GarbageConfigOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageConfigOpts a
tfield GarbageConfigOpts -> NumberProbability
_gcoLibraries Key
"items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageConfigOpts
(Double -> Double -> Double -> Double -> GarbageConfigOpts)
-> Codec GarbageConfigOpts Double
-> Codec
GarbageConfigOpts (Double -> Double -> Double -> GarbageConfigOpts)
forall a b.
Codec GarbageConfigOpts (a -> b)
-> Codec GarbageConfigOpts a -> Codec GarbageConfigOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageConfigOpts -> Double)
-> Key -> Codec GarbageConfigOpts Double
dfield GarbageConfigOpts -> Double
_gcoCell_Inst Key
"cell_or_inst"
Codec
GarbageConfigOpts (Double -> Double -> Double -> GarbageConfigOpts)
-> Codec GarbageConfigOpts Double
-> Codec GarbageConfigOpts (Double -> Double -> GarbageConfigOpts)
forall a b.
Codec GarbageConfigOpts (a -> b)
-> Codec GarbageConfigOpts a -> Codec GarbageConfigOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageConfigOpts -> Double)
-> Key -> Codec GarbageConfigOpts Double
dfield GarbageConfigOpts -> Double
_gcoLiblist_Use Key
"liblist_or_use"
Codec GarbageConfigOpts (Double -> Double -> GarbageConfigOpts)
-> Codec GarbageConfigOpts Double
-> Codec GarbageConfigOpts (Double -> GarbageConfigOpts)
forall a b.
Codec GarbageConfigOpts (a -> b)
-> Codec GarbageConfigOpts a -> Codec GarbageConfigOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageConfigOpts -> Double)
-> Key -> Codec GarbageConfigOpts Double
dfield GarbageConfigOpts -> Double
_gcoConfig Key
"config"
Codec GarbageConfigOpts (Double -> GarbageConfigOpts)
-> Codec GarbageConfigOpts Double -> TomlCodec GarbageConfigOpts
forall a b.
Codec GarbageConfigOpts (a -> b)
-> Codec GarbageConfigOpts a -> Codec GarbageConfigOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageConfigOpts -> Double)
-> Key -> Codec GarbageConfigOpts Double
dfield GarbageConfigOpts -> Double
_gcoLibraryScope Key
"libraryScope"
where
tfield :: (GarbageConfigOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageConfigOpts a
tfield GarbageConfigOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageConfigOpts -> a
p (GarbageConfigOpts -> a) -> GarbageConfigOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageConfigOpts
_goConfig (GarbageOpts -> GarbageConfigOpts)
-> GarbageOpts -> GarbageConfigOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a
-> (GarbageConfigOpts -> a) -> Codec GarbageConfigOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageConfigOpts -> a
p
dfield :: (GarbageConfigOpts -> Double)
-> Key -> Codec GarbageConfigOpts Double
dfield GarbageConfigOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageConfigOpts -> Double
p (GarbageConfigOpts -> Double) -> GarbageConfigOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageConfigOpts
_goConfig (GarbageOpts -> GarbageConfigOpts)
-> GarbageOpts -> GarbageConfigOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageConfigOpts -> Double) -> Codec GarbageConfigOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageConfigOpts -> Double
p
garbagePrimitiveCodec :: TomlCodec GarbagePrimitiveOpts
garbagePrimitiveCodec :: TomlCodec GarbagePrimitiveOpts
garbagePrimitiveCodec =
NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts
GarbagePrimitiveOpts
(NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts NumberProbability
-> Codec
GarbagePrimitiveOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbagePrimitiveOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbagePrimitiveOpts NumberProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> NumberProbability
_gpoBlocks Key
"blocks" TomlCodec NumberProbability
numProbCodec
Codec
GarbagePrimitiveOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts NumberProbability
-> Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbagePrimitiveOpts NumberProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> NumberProbability
_gpoPorts Key
"ports" TomlCodec NumberProbability
numProbCodec
Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts CategoricalProbability
-> Codec
GarbagePrimitiveOpts
(Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbagePrimitiveOpts CategoricalProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> CategoricalProbability
_gpoPortType Key
"portType" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbagePrimitiveOpts
(Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts Double
-> Codec
GarbagePrimitiveOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> Double)
-> Key -> Codec GarbagePrimitiveOpts Double
dfield GarbagePrimitiveOpts -> Double
_gpoSeq_Comb Key
"seq_or_comb"
Codec
GarbagePrimitiveOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts Double
-> Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> Double)
-> Key -> Codec GarbagePrimitiveOpts Double
dfield GarbagePrimitiveOpts -> Double
_gpoRegInit Key
"regInitNoSem"
Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts CategoricalProbability
-> Codec
GarbagePrimitiveOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbagePrimitiveOpts CategoricalProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> CategoricalProbability
_gpoCombInit Key
"combInit" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbagePrimitiveOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts NumberProbability
-> Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbagePrimitiveOpts NumberProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> NumberProbability
_gpoTableRows Key
"tableRows" TomlCodec NumberProbability
numProbCodec
Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts CategoricalProbability
-> Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbagePrimitiveOpts CategoricalProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> CategoricalProbability
_gpoInLevel Key
"inLevel" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbagePrimitiveOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts CategoricalProbability
-> Codec
GarbagePrimitiveOpts
(Double
-> CategoricalProbability -> Double -> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbagePrimitiveOpts CategoricalProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> CategoricalProbability
_gpoOutLevel Key
"outLevel" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbagePrimitiveOpts
(Double
-> CategoricalProbability -> Double -> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts Double
-> Codec
GarbagePrimitiveOpts
(CategoricalProbability -> Double -> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> Double)
-> Key -> Codec GarbagePrimitiveOpts Double
dfield GarbagePrimitiveOpts -> Double
_gpoEdgeSensitive Key
"edgeSensitive"
Codec
GarbagePrimitiveOpts
(CategoricalProbability -> Double -> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts CategoricalProbability
-> Codec GarbagePrimitiveOpts (Double -> GarbagePrimitiveOpts)
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbagePrimitiveOpts CategoricalProbability
forall {a}.
(GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> CategoricalProbability
_gpoEdgeSimplePosNeg Key
"edgeSimplePosNeg" TomlCodec CategoricalProbability
catProbCodec
Codec GarbagePrimitiveOpts (Double -> GarbagePrimitiveOpts)
-> Codec GarbagePrimitiveOpts Double
-> TomlCodec GarbagePrimitiveOpts
forall a b.
Codec GarbagePrimitiveOpts (a -> b)
-> Codec GarbagePrimitiveOpts a -> Codec GarbagePrimitiveOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbagePrimitiveOpts -> Double)
-> Key -> Codec GarbagePrimitiveOpts Double
dfield GarbagePrimitiveOpts -> Double
_gpoOutputNoChange Key
"outputNoChange"
where
tfield :: (GarbagePrimitiveOpts -> a)
-> Key -> TomlCodec a -> Codec GarbagePrimitiveOpts a
tfield GarbagePrimitiveOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbagePrimitiveOpts -> a
p (GarbagePrimitiveOpts -> a) -> GarbagePrimitiveOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbagePrimitiveOpts
_goPrimitive (GarbageOpts -> GarbagePrimitiveOpts)
-> GarbageOpts -> GarbagePrimitiveOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a
-> (GarbagePrimitiveOpts -> a) -> Codec GarbagePrimitiveOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbagePrimitiveOpts -> a
p
dfield :: (GarbagePrimitiveOpts -> Double)
-> Key -> Codec GarbagePrimitiveOpts Double
dfield GarbagePrimitiveOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbagePrimitiveOpts -> Double
p (GarbagePrimitiveOpts -> Double) -> GarbagePrimitiveOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbagePrimitiveOpts
_goPrimitive (GarbageOpts -> GarbagePrimitiveOpts)
-> GarbageOpts -> GarbagePrimitiveOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbagePrimitiveOpts -> Double)
-> Codec GarbagePrimitiveOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbagePrimitiveOpts -> Double
p
garbageModuleCodec :: TomlCodec GarbageModuleOpts
garbageModuleCodec :: TomlCodec GarbageModuleOpts
garbageModuleCodec =
NumberProbability
-> Double
-> NumberProbability
-> Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts
GarbageModuleOpts
(NumberProbability
-> Double
-> NumberProbability
-> Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts NumberProbability
-> Codec
GarbageModuleOpts
(Double
-> NumberProbability
-> Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageModuleOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageModuleOpts NumberProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> NumberProbability
_gmoBlocks Key
"blocks" TomlCodec NumberProbability
numProbCodec
Codec
GarbageModuleOpts
(Double
-> NumberProbability
-> Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts Double
-> Codec
GarbageModuleOpts
(NumberProbability
-> Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> Double)
-> Key -> Codec GarbageModuleOpts Double
dfield GarbageModuleOpts -> Double
_gmoNamed_Positional Key
"instance_named_or_positional"
Codec
GarbageModuleOpts
(NumberProbability
-> Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts NumberProbability
-> Codec
GarbageModuleOpts
(Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageModuleOpts NumberProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> NumberProbability
_gmoParameters Key
"instance_parameters" TomlCodec NumberProbability
numProbCodec
Codec
GarbageModuleOpts
(Double
-> NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts Double
-> Codec
GarbageModuleOpts
(NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> Double)
-> Key -> Codec GarbageModuleOpts Double
dfield GarbageModuleOpts -> Double
_gmoOptionalParameter Key
"instance_optparam"
Codec
GarbageModuleOpts
(NumberProbability
-> NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts NumberProbability
-> Codec
GarbageModuleOpts
(NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageModuleOpts NumberProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> NumberProbability
_gmoPorts Key
"port_count" TomlCodec NumberProbability
numProbCodec
Codec
GarbageModuleOpts
(NumberProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts NumberProbability
-> Codec
GarbageModuleOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageModuleOpts NumberProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> NumberProbability
_gmoPortLValues Key
"port_lvalues" TomlCodec NumberProbability
numProbCodec
Codec
GarbageModuleOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts Double
-> Codec
GarbageModuleOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> Double)
-> Key -> Codec GarbageModuleOpts Double
dfield GarbageModuleOpts -> Double
_gmoPortRange Key
"port_range"
Codec
GarbageModuleOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts CategoricalProbability
-> Codec
GarbageModuleOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageModuleOpts CategoricalProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> CategoricalProbability
_gmoPortDir Key
"port_dir" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageModuleOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts Double
-> Codec
GarbageModuleOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> Double)
-> Key -> Codec GarbageModuleOpts Double
dfield GarbageModuleOpts -> Double
_gmoOptionalPort Key
"port_optional"
Codec
GarbageModuleOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts NumberProbability
-> Codec
GarbageModuleOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageModuleOpts NumberProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> NumberProbability
_gmoItems Key
"items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageModuleOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts CategoricalProbability
-> Codec
GarbageModuleOpts
(Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageModuleOpts CategoricalProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> CategoricalProbability
_gmoItem Key
"item" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageModuleOpts
(Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts Double
-> Codec
GarbageModuleOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> Double)
-> Key -> Codec GarbageModuleOpts Double
dfield GarbageModuleOpts -> Double
_gmoTimeScale Key
"timescale_optional"
Codec
GarbageModuleOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts CategoricalProbability
-> Codec
GarbageModuleOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageModuleOpts CategoricalProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> CategoricalProbability
_gmoTimeMagnitude Key
"timescale_magnitude" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageModuleOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> Bool
-> GarbageModuleOpts)
-> Codec GarbageModuleOpts Double
-> Codec
GarbageModuleOpts
(CategoricalProbability
-> CategoricalProbability -> Bool -> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> Double)
-> Key -> Codec GarbageModuleOpts Double
dfield GarbageModuleOpts -> Double
_gmoCell Key
"cell"
Codec
GarbageModuleOpts
(CategoricalProbability
-> CategoricalProbability -> Bool -> GarbageModuleOpts)
-> Codec GarbageModuleOpts CategoricalProbability
-> Codec
GarbageModuleOpts
(CategoricalProbability -> Bool -> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageModuleOpts CategoricalProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> CategoricalProbability
_gmoUnconnectedDrive Key
"unconnectedDrive" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageModuleOpts
(CategoricalProbability -> Bool -> GarbageModuleOpts)
-> Codec GarbageModuleOpts CategoricalProbability
-> Codec GarbageModuleOpts (Bool -> GarbageModuleOpts)
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageModuleOpts CategoricalProbability
forall {a}.
(GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> CategoricalProbability
_gmoDefaultNetType Key
"defaultNetType" TomlCodec CategoricalProbability
catProbCodec
Codec GarbageModuleOpts (Bool -> GarbageModuleOpts)
-> Codec GarbageModuleOpts Bool -> TomlCodec GarbageModuleOpts
forall a b.
Codec GarbageModuleOpts (a -> b)
-> Codec GarbageModuleOpts a -> Codec GarbageModuleOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageModuleOpts -> Bool) -> Key -> Codec GarbageModuleOpts Bool
bfield GarbageModuleOpts -> Bool
_gmoNonAsciiHeader Key
"nonAsciiHeader"
where
tfield :: (GarbageModuleOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageModuleOpts a
tfield GarbageModuleOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageModuleOpts -> a
p (GarbageModuleOpts -> a) -> GarbageModuleOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageModuleOpts
_goModule (GarbageOpts -> GarbageModuleOpts)
-> GarbageOpts -> GarbageModuleOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a
-> (GarbageModuleOpts -> a) -> Codec GarbageModuleOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageModuleOpts -> a
p
dfield :: (GarbageModuleOpts -> Double)
-> Key -> Codec GarbageModuleOpts Double
dfield GarbageModuleOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageModuleOpts -> Double
p (GarbageModuleOpts -> Double) -> GarbageModuleOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageModuleOpts
_goModule (GarbageOpts -> GarbageModuleOpts)
-> GarbageOpts -> GarbageModuleOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageModuleOpts -> Double) -> Codec GarbageModuleOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageModuleOpts -> Double
p
bfield :: (GarbageModuleOpts -> Bool) -> Key -> Codec GarbageModuleOpts Bool
bfield GarbageModuleOpts -> Bool
p Key
n =
Bool -> TomlCodec Bool -> TomlCodec Bool
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageModuleOpts -> Bool
p (GarbageModuleOpts -> Bool) -> GarbageModuleOpts -> Bool
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageModuleOpts
_goModule (GarbageOpts -> GarbageModuleOpts)
-> GarbageOpts -> GarbageModuleOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Bool
Toml.bool Key
n) TomlCodec Bool
-> (GarbageModuleOpts -> Bool) -> Codec GarbageModuleOpts Bool
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageModuleOpts -> Bool
p
garbageSpecifyPathCodec :: TomlCodec GarbageSpecifyPathOpts
garbageSpecifyPathCodec :: TomlCodec GarbageSpecifyPathOpts
garbageSpecifyPathCodec =
CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts
GarbageSpecifyPathOpts
(CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts CategoricalProbability
-> Codec
GarbageSpecifyPathOpts
(Double
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageSpecifyPathOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageSpecifyPathOpts CategoricalProbability
forall {a}.
(GarbageSpecifyPathOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyPathOpts a
tfield GarbageSpecifyPathOpts -> CategoricalProbability
_gspoCondition Key
"condition" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageSpecifyPathOpts
(Double
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts Double
-> Codec
GarbageSpecifyPathOpts
(Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
forall a b.
Codec GarbageSpecifyPathOpts (a -> b)
-> Codec GarbageSpecifyPathOpts a -> Codec GarbageSpecifyPathOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyPathOpts -> Double)
-> Key -> Codec GarbageSpecifyPathOpts Double
dfield GarbageSpecifyPathOpts -> Double
_gspoFull_Parallel Key
"full_or_parallel"
Codec
GarbageSpecifyPathOpts
(Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts Double
-> Codec
GarbageSpecifyPathOpts
(NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
forall a b.
Codec GarbageSpecifyPathOpts (a -> b)
-> Codec GarbageSpecifyPathOpts a -> Codec GarbageSpecifyPathOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyPathOpts -> Double)
-> Key -> Codec GarbageSpecifyPathOpts Double
dfield GarbageSpecifyPathOpts -> Double
_gspoEdgeSensitive Key
"edgeSensitive"
Codec
GarbageSpecifyPathOpts
(NumberProbability
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts NumberProbability
-> Codec
GarbageSpecifyPathOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
forall a b.
Codec GarbageSpecifyPathOpts (a -> b)
-> Codec GarbageSpecifyPathOpts a -> Codec GarbageSpecifyPathOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyPathOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageSpecifyPathOpts NumberProbability
forall {a}.
(GarbageSpecifyPathOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyPathOpts a
tfield GarbageSpecifyPathOpts -> NumberProbability
_gspoFullSources Key
"full_sources" TomlCodec NumberProbability
numProbCodec
Codec
GarbageSpecifyPathOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts NumberProbability
-> Codec
GarbageSpecifyPathOpts
(CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
forall a b.
Codec GarbageSpecifyPathOpts (a -> b)
-> Codec GarbageSpecifyPathOpts a -> Codec GarbageSpecifyPathOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyPathOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageSpecifyPathOpts NumberProbability
forall {a}.
(GarbageSpecifyPathOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyPathOpts a
tfield GarbageSpecifyPathOpts -> NumberProbability
_gspoFullDestinations Key
"full_destinations" TomlCodec NumberProbability
numProbCodec
Codec
GarbageSpecifyPathOpts
(CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts CategoricalProbability
-> Codec
GarbageSpecifyPathOpts
(CategoricalProbability
-> CategoricalProbability -> GarbageSpecifyPathOpts)
forall a b.
Codec GarbageSpecifyPathOpts (a -> b)
-> Codec GarbageSpecifyPathOpts a -> Codec GarbageSpecifyPathOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyPathOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageSpecifyPathOpts CategoricalProbability
forall {a}.
(GarbageSpecifyPathOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyPathOpts a
tfield GarbageSpecifyPathOpts -> CategoricalProbability
_gspoPolarity Key
"polarity" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageSpecifyPathOpts
(CategoricalProbability
-> CategoricalProbability -> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts CategoricalProbability
-> Codec
GarbageSpecifyPathOpts
(CategoricalProbability -> GarbageSpecifyPathOpts)
forall a b.
Codec GarbageSpecifyPathOpts (a -> b)
-> Codec GarbageSpecifyPathOpts a -> Codec GarbageSpecifyPathOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyPathOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageSpecifyPathOpts CategoricalProbability
forall {a}.
(GarbageSpecifyPathOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyPathOpts a
tfield GarbageSpecifyPathOpts -> CategoricalProbability
_gspoEdgeSensitivity Key
"edgeSensitivity" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageSpecifyPathOpts
(CategoricalProbability -> GarbageSpecifyPathOpts)
-> Codec GarbageSpecifyPathOpts CategoricalProbability
-> TomlCodec GarbageSpecifyPathOpts
forall a b.
Codec GarbageSpecifyPathOpts (a -> b)
-> Codec GarbageSpecifyPathOpts a -> Codec GarbageSpecifyPathOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyPathOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageSpecifyPathOpts CategoricalProbability
forall {a}.
(GarbageSpecifyPathOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyPathOpts a
tfield GarbageSpecifyPathOpts -> CategoricalProbability
_gspoDelayKind Key
"delayKind" TomlCodec CategoricalProbability
catProbCodec
where
tfield :: (GarbageSpecifyPathOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyPathOpts a
tfield GarbageSpecifyPathOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(GarbageSpecifyPathOpts -> a
p (GarbageSpecifyPathOpts -> a) -> GarbageSpecifyPathOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageSpecifyOpts -> GarbageSpecifyPathOpts
_gsyoPath (GarbageSpecifyOpts -> GarbageSpecifyPathOpts)
-> GarbageSpecifyOpts -> GarbageSpecifyPathOpts
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageSpecifyOpts
_goSpecify (GarbageOpts -> GarbageSpecifyOpts)
-> GarbageOpts -> GarbageSpecifyOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig)
(TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n)
TomlCodec a
-> (GarbageSpecifyPathOpts -> a) -> Codec GarbageSpecifyPathOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageSpecifyPathOpts -> a
p
dfield :: (GarbageSpecifyPathOpts -> Double)
-> Key -> Codec GarbageSpecifyPathOpts Double
dfield GarbageSpecifyPathOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(GarbageSpecifyPathOpts -> Double
p (GarbageSpecifyPathOpts -> Double)
-> GarbageSpecifyPathOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageSpecifyOpts -> GarbageSpecifyPathOpts
_gsyoPath (GarbageSpecifyOpts -> GarbageSpecifyPathOpts)
-> GarbageSpecifyOpts -> GarbageSpecifyPathOpts
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageSpecifyOpts
_goSpecify (GarbageOpts -> GarbageSpecifyOpts)
-> GarbageOpts -> GarbageSpecifyOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig)
(Key -> TomlCodec Double
Toml.double Key
n)
TomlCodec Double
-> (GarbageSpecifyPathOpts -> Double)
-> Codec GarbageSpecifyPathOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageSpecifyPathOpts -> Double
p
garbageSpecifyTimingCheckCodec :: TomlCodec GarbageSpecifyTimingCheckOpts
garbageSpecifyTimingCheckCodec :: TomlCodec GarbageSpecifyTimingCheckOpts
garbageSpecifyTimingCheckCodec =
Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyTimingCheckOpts
GarbageSpecifyTimingCheckOpts
(Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyTimingCheckOpts)
-> Codec GarbageSpecifyTimingCheckOpts Double
-> Codec
GarbageSpecifyTimingCheckOpts
(Double
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyTimingCheckOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageSpecifyTimingCheckOpts -> Double)
-> Key -> Codec GarbageSpecifyTimingCheckOpts Double
dfield GarbageSpecifyTimingCheckOpts -> Double
_gstcoOptionalArg Key
"optarg"
Codec
GarbageSpecifyTimingCheckOpts
(Double
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyTimingCheckOpts)
-> Codec GarbageSpecifyTimingCheckOpts Double
-> Codec
GarbageSpecifyTimingCheckOpts
(Double
-> Double -> Double -> Double -> GarbageSpecifyTimingCheckOpts)
forall a b.
Codec GarbageSpecifyTimingCheckOpts (a -> b)
-> Codec GarbageSpecifyTimingCheckOpts a
-> Codec GarbageSpecifyTimingCheckOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyTimingCheckOpts -> Double)
-> Key -> Codec GarbageSpecifyTimingCheckOpts Double
dfield GarbageSpecifyTimingCheckOpts -> Double
_gstcoEvent Key
"event_optional"
Codec
GarbageSpecifyTimingCheckOpts
(Double
-> Double -> Double -> Double -> GarbageSpecifyTimingCheckOpts)
-> Codec GarbageSpecifyTimingCheckOpts Double
-> Codec
GarbageSpecifyTimingCheckOpts
(Double -> Double -> Double -> GarbageSpecifyTimingCheckOpts)
forall a b.
Codec GarbageSpecifyTimingCheckOpts (a -> b)
-> Codec GarbageSpecifyTimingCheckOpts a
-> Codec GarbageSpecifyTimingCheckOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyTimingCheckOpts -> Double)
-> Key -> Codec GarbageSpecifyTimingCheckOpts Double
dfield GarbageSpecifyTimingCheckOpts -> Double
_gstcoEventEdge Key
"event_edge"
Codec
GarbageSpecifyTimingCheckOpts
(Double -> Double -> Double -> GarbageSpecifyTimingCheckOpts)
-> Codec GarbageSpecifyTimingCheckOpts Double
-> Codec
GarbageSpecifyTimingCheckOpts
(Double -> Double -> GarbageSpecifyTimingCheckOpts)
forall a b.
Codec GarbageSpecifyTimingCheckOpts (a -> b)
-> Codec GarbageSpecifyTimingCheckOpts a
-> Codec GarbageSpecifyTimingCheckOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyTimingCheckOpts -> Double)
-> Key -> Codec GarbageSpecifyTimingCheckOpts Double
dfield GarbageSpecifyTimingCheckOpts -> Double
_gstcoCondition Key
"condition_optional"
Codec
GarbageSpecifyTimingCheckOpts
(Double -> Double -> GarbageSpecifyTimingCheckOpts)
-> Codec GarbageSpecifyTimingCheckOpts Double
-> Codec
GarbageSpecifyTimingCheckOpts
(Double -> GarbageSpecifyTimingCheckOpts)
forall a b.
Codec GarbageSpecifyTimingCheckOpts (a -> b)
-> Codec GarbageSpecifyTimingCheckOpts a
-> Codec GarbageSpecifyTimingCheckOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyTimingCheckOpts -> Double)
-> Key -> Codec GarbageSpecifyTimingCheckOpts Double
dfield GarbageSpecifyTimingCheckOpts -> Double
_gstcoCondNeg_Pos Key
"condition_neg_or_pos"
Codec
GarbageSpecifyTimingCheckOpts
(Double -> GarbageSpecifyTimingCheckOpts)
-> Codec GarbageSpecifyTimingCheckOpts Double
-> TomlCodec GarbageSpecifyTimingCheckOpts
forall a b.
Codec GarbageSpecifyTimingCheckOpts (a -> b)
-> Codec GarbageSpecifyTimingCheckOpts a
-> Codec GarbageSpecifyTimingCheckOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyTimingCheckOpts -> Double)
-> Key -> Codec GarbageSpecifyTimingCheckOpts Double
dfield GarbageSpecifyTimingCheckOpts -> Double
_gstcoDelayedMinTypMax Key
"delayedMinTypMax"
where
dfield :: (GarbageSpecifyTimingCheckOpts -> Double)
-> Key -> Codec GarbageSpecifyTimingCheckOpts Double
dfield GarbageSpecifyTimingCheckOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(GarbageSpecifyTimingCheckOpts -> Double
p (GarbageSpecifyTimingCheckOpts -> Double)
-> GarbageSpecifyTimingCheckOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts
_gsyoTimingCheck (GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts)
-> GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageSpecifyOpts
_goSpecify (GarbageOpts -> GarbageSpecifyOpts)
-> GarbageOpts -> GarbageSpecifyOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig)
(Key -> TomlCodec Double
Toml.double Key
n)
TomlCodec Double
-> (GarbageSpecifyTimingCheckOpts -> Double)
-> Codec GarbageSpecifyTimingCheckOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageSpecifyTimingCheckOpts -> Double
p
garbageSpecifyCodec :: TomlCodec GarbageSpecifyOpts
garbageSpecifyCodec :: TomlCodec GarbageSpecifyOpts
garbageSpecifyCodec =
GarbageSpecifyPathOpts
-> GarbageSpecifyTimingCheckOpts
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyOpts
GarbageSpecifyOpts
(GarbageSpecifyPathOpts
-> GarbageSpecifyTimingCheckOpts
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts GarbageSpecifyPathOpts
-> Codec
GarbageSpecifyOpts
(GarbageSpecifyTimingCheckOpts
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageSpecifyOpts -> GarbageSpecifyPathOpts)
-> Key
-> TomlCodec GarbageSpecifyPathOpts
-> Codec GarbageSpecifyOpts GarbageSpecifyPathOpts
forall {a}.
(GarbageSpecifyOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyOpts a
tfield GarbageSpecifyOpts -> GarbageSpecifyPathOpts
_gsyoPath Key
"path" TomlCodec GarbageSpecifyPathOpts
garbageSpecifyPathCodec
Codec
GarbageSpecifyOpts
(GarbageSpecifyTimingCheckOpts
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts GarbageSpecifyTimingCheckOpts
-> Codec
GarbageSpecifyOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyOpts)
forall a b.
Codec GarbageSpecifyOpts (a -> b)
-> Codec GarbageSpecifyOpts a -> Codec GarbageSpecifyOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts)
-> Key
-> TomlCodec GarbageSpecifyTimingCheckOpts
-> Codec GarbageSpecifyOpts GarbageSpecifyTimingCheckOpts
forall {a}.
(GarbageSpecifyOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyOpts a
tfield GarbageSpecifyOpts -> GarbageSpecifyTimingCheckOpts
_gsyoTimingCheck Key
"timingCheck" TomlCodec GarbageSpecifyTimingCheckOpts
garbageSpecifyTimingCheckCodec
Codec
GarbageSpecifyOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts NumberProbability
-> Codec
GarbageSpecifyOpts
(CategoricalProbability
-> Double -> Double -> Double -> Double -> GarbageSpecifyOpts)
forall a b.
Codec GarbageSpecifyOpts (a -> b)
-> Codec GarbageSpecifyOpts a -> Codec GarbageSpecifyOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageSpecifyOpts NumberProbability
forall {a}.
(GarbageSpecifyOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyOpts a
tfield GarbageSpecifyOpts -> NumberProbability
_gsyoItems Key
"items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageSpecifyOpts
(CategoricalProbability
-> Double -> Double -> Double -> Double -> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts CategoricalProbability
-> Codec
GarbageSpecifyOpts
(Double -> Double -> Double -> Double -> GarbageSpecifyOpts)
forall a b.
Codec GarbageSpecifyOpts (a -> b)
-> Codec GarbageSpecifyOpts a -> Codec GarbageSpecifyOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageSpecifyOpts CategoricalProbability
forall {a}.
(GarbageSpecifyOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyOpts a
tfield GarbageSpecifyOpts -> CategoricalProbability
_gsyoItem Key
"item" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageSpecifyOpts
(Double -> Double -> Double -> Double -> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts Double
-> Codec
GarbageSpecifyOpts
(Double -> Double -> Double -> GarbageSpecifyOpts)
forall a b.
Codec GarbageSpecifyOpts (a -> b)
-> Codec GarbageSpecifyOpts a -> Codec GarbageSpecifyOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyOpts -> Double)
-> Key -> Codec GarbageSpecifyOpts Double
dfield GarbageSpecifyOpts -> Double
_gsyoTermRange Key
"termRange"
Codec
GarbageSpecifyOpts
(Double -> Double -> Double -> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts Double
-> Codec
GarbageSpecifyOpts (Double -> Double -> GarbageSpecifyOpts)
forall a b.
Codec GarbageSpecifyOpts (a -> b)
-> Codec GarbageSpecifyOpts a -> Codec GarbageSpecifyOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyOpts -> Double)
-> Key -> Codec GarbageSpecifyOpts Double
dfield GarbageSpecifyOpts -> Double
_gsyoParamRange Key
"parameter_range"
Codec GarbageSpecifyOpts (Double -> Double -> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts Double
-> Codec GarbageSpecifyOpts (Double -> GarbageSpecifyOpts)
forall a b.
Codec GarbageSpecifyOpts (a -> b)
-> Codec GarbageSpecifyOpts a -> Codec GarbageSpecifyOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyOpts -> Double)
-> Key -> Codec GarbageSpecifyOpts Double
dfield GarbageSpecifyOpts -> Double
_gsyoPathPulseEscaped_Simple Key
"pathpulse_escaped_or_simple"
Codec GarbageSpecifyOpts (Double -> GarbageSpecifyOpts)
-> Codec GarbageSpecifyOpts Double -> TomlCodec GarbageSpecifyOpts
forall a b.
Codec GarbageSpecifyOpts (a -> b)
-> Codec GarbageSpecifyOpts a -> Codec GarbageSpecifyOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageSpecifyOpts -> Double)
-> Key -> Codec GarbageSpecifyOpts Double
dfield GarbageSpecifyOpts -> Double
_gsyoPathPulseRange Key
"pathpulse_term_range"
where
tfield :: (GarbageSpecifyOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageSpecifyOpts a
tfield GarbageSpecifyOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageSpecifyOpts -> a
p (GarbageSpecifyOpts -> a) -> GarbageSpecifyOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageSpecifyOpts
_goSpecify (GarbageOpts -> GarbageSpecifyOpts)
-> GarbageOpts -> GarbageSpecifyOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a
-> (GarbageSpecifyOpts -> a) -> Codec GarbageSpecifyOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageSpecifyOpts -> a
p
dfield :: (GarbageSpecifyOpts -> Double)
-> Key -> Codec GarbageSpecifyOpts Double
dfield GarbageSpecifyOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageSpecifyOpts -> Double
p (GarbageSpecifyOpts -> Double) -> GarbageSpecifyOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageSpecifyOpts
_goSpecify (GarbageOpts -> GarbageSpecifyOpts)
-> GarbageOpts -> GarbageSpecifyOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageSpecifyOpts -> Double)
-> Codec GarbageSpecifyOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageSpecifyOpts -> Double
p
garbageGenerateCodec :: TomlCodec GarbageGenerateOpts
garbageGenerateCodec :: TomlCodec GarbageGenerateOpts
garbageGenerateCodec =
GarbageAttenuationOpts
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts
GarbageGenerateOpts
(GarbageAttenuationOpts
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts GarbageAttenuationOpts
-> Codec
GarbageGenerateOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec GarbageAttenuationOpts
garbageAttenuationCodec Key
"attenuation" TomlCodec GarbageAttenuationOpts
-> (GarbageGenerateOpts -> GarbageAttenuationOpts)
-> Codec GarbageGenerateOpts GarbageAttenuationOpts
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageGenerateOpts -> GarbageAttenuationOpts
_ggoAttenuation
Codec
GarbageGenerateOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts NumberProbability
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageGenerateOpts NumberProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> NumberProbability
_ggoItems Key
"items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoItem Key
"item" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(Double
-> Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoOptionalBlock Key
"optionalBlock"
Codec
GarbageGenerateOpts
(Double
-> Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoInstOptionalDelay Key
"instance_optional_delay"
Codec
GarbageGenerateOpts
(Double
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoInstOptionalRange Key
"instance_optional_range"
Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoPrimitiveOptIdent Key
"primitive_optional_name"
Codec
GarbageGenerateOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoCondBlock Key
"nested_condition" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoNetType Key
"net_type" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoNetRange Key
"net_range"
Codec
GarbageGenerateOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoNetVectoring Key
"net_vectoring" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoDeclItem Key
"declaration" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoDeclDim_Init Key
"declaration_dim_or_init"
Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoChargeStrength Key
"chargeStrength" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoTaskFunAutomatic Key
"taskFun_automatic"
Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoTaskFunDecl Key
"taskFun_declaration" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoTaskFunRegister Key
"taskFun_register"
Codec
GarbageGenerateOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts NumberProbability
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageGenerateOpts NumberProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> NumberProbability
_ggoTaskFunPorts Key
"taskFun_ports" TomlCodec NumberProbability
numProbCodec
Codec
GarbageGenerateOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoTaskFunPortType Key
"taskFun_portType" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoTaskPortDirection Key
"taskPortDir" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoFunRetType Key
"funReturnType"
Codec
GarbageGenerateOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoGateInst Key
"gate" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts Double
-> Codec
GarbageGenerateOpts
(CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
_ggoGateOptIdent Key
"gate_optional_name"
Codec
GarbageGenerateOpts
(CategoricalProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts CategoricalProbability
-> Codec
GarbageGenerateOpts
(NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageGenerateOpts CategoricalProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> CategoricalProbability
_ggoGateNInputType Key
"gate_ninput" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageGenerateOpts
(NumberProbability
-> NumberProbability
-> NumberProbability
-> NumberProbability
-> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts NumberProbability
-> Codec
GarbageGenerateOpts
(NumberProbability
-> NumberProbability -> NumberProbability -> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageGenerateOpts NumberProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> NumberProbability
_ggoGateInputs Key
"gate_ninputs" TomlCodec NumberProbability
numProbCodec
Codec
GarbageGenerateOpts
(NumberProbability
-> NumberProbability -> NumberProbability -> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts NumberProbability
-> Codec
GarbageGenerateOpts
(NumberProbability -> NumberProbability -> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageGenerateOpts NumberProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> NumberProbability
_ggoGateOutputs Key
"gate_noutputs" TomlCodec NumberProbability
numProbCodec
Codec
GarbageGenerateOpts
(NumberProbability -> NumberProbability -> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts NumberProbability
-> Codec
GarbageGenerateOpts (NumberProbability -> GarbageGenerateOpts)
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageGenerateOpts NumberProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> NumberProbability
_ggoCaseBranches Key
"case_branches" TomlCodec NumberProbability
numProbCodec
Codec
GarbageGenerateOpts (NumberProbability -> GarbageGenerateOpts)
-> Codec GarbageGenerateOpts NumberProbability
-> TomlCodec GarbageGenerateOpts
forall a b.
Codec GarbageGenerateOpts (a -> b)
-> Codec GarbageGenerateOpts a -> Codec GarbageGenerateOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageGenerateOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageGenerateOpts NumberProbability
forall {a}.
(GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> NumberProbability
_ggoCaseBranchPatterns Key
"case_patterns" TomlCodec NumberProbability
numProbCodec
where
tfield :: (GarbageGenerateOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageGenerateOpts a
tfield GarbageGenerateOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageGenerateOpts -> a
p (GarbageGenerateOpts -> a) -> GarbageGenerateOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageGenerateOpts
_goGenerate (GarbageOpts -> GarbageGenerateOpts)
-> GarbageOpts -> GarbageGenerateOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a
-> (GarbageGenerateOpts -> a) -> Codec GarbageGenerateOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageGenerateOpts -> a
p
dfield :: (GarbageGenerateOpts -> Double)
-> Key -> Codec GarbageGenerateOpts Double
dfield GarbageGenerateOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageGenerateOpts -> Double
p (GarbageGenerateOpts -> Double) -> GarbageGenerateOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageGenerateOpts
_goGenerate (GarbageOpts -> GarbageGenerateOpts)
-> GarbageOpts -> GarbageGenerateOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageGenerateOpts -> Double)
-> Codec GarbageGenerateOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageGenerateOpts -> Double
p
garbageTypeCodec :: TomlCodec GarbageTypeOpts
garbageTypeCodec :: TomlCodec GarbageTypeOpts
garbageTypeCodec =
Double
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> GarbageTypeOpts
GarbageTypeOpts
(Double
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> GarbageTypeOpts)
-> Codec GarbageTypeOpts Double
-> Codec
GarbageTypeOpts
(CategoricalProbability
-> Double -> Double -> NumberProbability -> GarbageTypeOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageTypeOpts -> Double) -> Key -> Codec GarbageTypeOpts Double
dfield GarbageTypeOpts -> Double
_gtoAbstract_Concrete Key
"abstract_or_concrete"
Codec
GarbageTypeOpts
(CategoricalProbability
-> Double -> Double -> NumberProbability -> GarbageTypeOpts)
-> Codec GarbageTypeOpts CategoricalProbability
-> Codec
GarbageTypeOpts
(Double -> Double -> NumberProbability -> GarbageTypeOpts)
forall a b.
Codec GarbageTypeOpts (a -> b)
-> Codec GarbageTypeOpts a -> Codec GarbageTypeOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageTypeOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageTypeOpts CategoricalProbability
forall {a}.
(GarbageTypeOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageTypeOpts a
tfield GarbageTypeOpts -> CategoricalProbability
_gtoAbstract Key
"abstract" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageTypeOpts
(Double -> Double -> NumberProbability -> GarbageTypeOpts)
-> Codec GarbageTypeOpts Double
-> Codec
GarbageTypeOpts (Double -> NumberProbability -> GarbageTypeOpts)
forall a b.
Codec GarbageTypeOpts (a -> b)
-> Codec GarbageTypeOpts a -> Codec GarbageTypeOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageTypeOpts -> Double) -> Key -> Codec GarbageTypeOpts Double
dfield GarbageTypeOpts -> Double
_gtoConcreteSignedness Key
"concrete_signedness"
Codec
GarbageTypeOpts (Double -> NumberProbability -> GarbageTypeOpts)
-> Codec GarbageTypeOpts Double
-> Codec GarbageTypeOpts (NumberProbability -> GarbageTypeOpts)
forall a b.
Codec GarbageTypeOpts (a -> b)
-> Codec GarbageTypeOpts a -> Codec GarbageTypeOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageTypeOpts -> Double) -> Key -> Codec GarbageTypeOpts Double
dfield GarbageTypeOpts -> Double
_gtoConcreteBitRange Key
"concrete_bitRange"
Codec GarbageTypeOpts (NumberProbability -> GarbageTypeOpts)
-> Codec GarbageTypeOpts NumberProbability
-> TomlCodec GarbageTypeOpts
forall a b.
Codec GarbageTypeOpts (a -> b)
-> Codec GarbageTypeOpts a -> Codec GarbageTypeOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageTypeOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageTypeOpts NumberProbability
forall {a}.
(GarbageTypeOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageTypeOpts a
tfield GarbageTypeOpts -> NumberProbability
_gtoDimensions Key
"dimensions" TomlCodec NumberProbability
numProbCodec
where
tfield :: (GarbageTypeOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageTypeOpts a
tfield GarbageTypeOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageTypeOpts -> a
p (GarbageTypeOpts -> a) -> GarbageTypeOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageTypeOpts
_goType (GarbageOpts -> GarbageTypeOpts) -> GarbageOpts -> GarbageTypeOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a -> (GarbageTypeOpts -> a) -> Codec GarbageTypeOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageTypeOpts -> a
p
dfield :: (GarbageTypeOpts -> Double) -> Key -> Codec GarbageTypeOpts Double
dfield GarbageTypeOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageTypeOpts -> Double
p (GarbageTypeOpts -> Double) -> GarbageTypeOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageTypeOpts
_goType (GarbageOpts -> GarbageTypeOpts) -> GarbageOpts -> GarbageTypeOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageTypeOpts -> Double) -> Codec GarbageTypeOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageTypeOpts -> Double
p
garbageStatementCodec :: TomlCodec GarbageStatementOpts
garbageStatementCodec :: TomlCodec GarbageStatementOpts
garbageStatementCodec =
GarbageAttenuationOpts
-> Double
-> CategoricalProbability
-> NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts
GarbageStatementOpts
(GarbageAttenuationOpts
-> Double
-> CategoricalProbability
-> NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts GarbageAttenuationOpts
-> Codec
GarbageStatementOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec GarbageAttenuationOpts
garbageAttenuationCodec Key
"attenuation" TomlCodec GarbageAttenuationOpts
-> (GarbageStatementOpts -> GarbageAttenuationOpts)
-> Codec GarbageStatementOpts GarbageAttenuationOpts
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageStatementOpts -> GarbageAttenuationOpts
_gstoAttenuation
Codec
GarbageStatementOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts Double
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
_gstoOptional Key
"optional"
Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoItem Key
"item" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(NumberProbability
-> Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts NumberProbability
-> Codec
GarbageStatementOpts
(Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageStatementOpts NumberProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> NumberProbability
_gstoItems Key
"items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageStatementOpts
(Double
-> Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts Double
-> Codec
GarbageStatementOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
_gstoOptionalDelEvCtl Key
"optionalDelayEventControl"
Codec
GarbageStatementOpts
(Double
-> CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts Double
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
_gstoAssignmentBlocking Key
"assignmentBlocking"
Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoCase Key
"case_kind" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts NumberProbability
-> Codec
GarbageStatementOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageStatementOpts NumberProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> NumberProbability
_gstoCaseBranches Key
"case_branches" TomlCodec NumberProbability
numProbCodec
Codec
GarbageStatementOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts NumberProbability
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageStatementOpts NumberProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> NumberProbability
_gstoCaseBranchPatterns Key
"case_patterns" TomlCodec NumberProbability
numProbCodec
Codec
GarbageStatementOpts
(CategoricalProbability
-> Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoLoop Key
"loop" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(Double
-> Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts Double
-> Codec
GarbageStatementOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
_gstoBlockPar_Seq Key
"block_par_or_seq"
Codec
GarbageStatementOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts Double
-> Codec
GarbageStatementOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
_gstoBlockHeader Key
"block_header"
Codec
GarbageStatementOpts
(NumberProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts NumberProbability
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageStatementOpts NumberProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> NumberProbability
_gstoBlockDecls Key
"block_declarations" TomlCodec NumberProbability
numProbCodec
Codec
GarbageStatementOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoBlockDecl Key
"block_declaration" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoProcContAssign Key
"procContAss_assDeassForceRel" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts Double
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
_gstoPCAVar_Net Key
"procContAss_var_or_net"
Codec
GarbageStatementOpts
(CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoDelayEventRepeat Key
"delayEventRepeat" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoEvent Key
"event" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageStatementOpts)
-> Codec GarbageStatementOpts NumberProbability
-> Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability -> Double -> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageStatementOpts NumberProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> NumberProbability
_gstoEvents Key
"event_exprs" TomlCodec NumberProbability
numProbCodec
Codec
GarbageStatementOpts
(CategoricalProbability
-> NumberProbability -> Double -> GarbageStatementOpts)
-> Codec GarbageStatementOpts CategoricalProbability
-> Codec
GarbageStatementOpts
(NumberProbability -> Double -> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageStatementOpts CategoricalProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> CategoricalProbability
_gstoEventPrefix Key
"event_prefix" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageStatementOpts
(NumberProbability -> Double -> GarbageStatementOpts)
-> Codec GarbageStatementOpts NumberProbability
-> Codec GarbageStatementOpts (Double -> GarbageStatementOpts)
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageStatementOpts NumberProbability
forall {a}.
(GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> NumberProbability
_gstoSysTaskPorts Key
"sysTask_ports" TomlCodec NumberProbability
numProbCodec
Codec GarbageStatementOpts (Double -> GarbageStatementOpts)
-> Codec GarbageStatementOpts Double
-> TomlCodec GarbageStatementOpts
forall a b.
Codec GarbageStatementOpts (a -> b)
-> Codec GarbageStatementOpts a -> Codec GarbageStatementOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
_gstoSysTaskOptionalPort Key
"sysTask_optionalPort"
where
tfield :: (GarbageStatementOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageStatementOpts a
tfield GarbageStatementOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageStatementOpts -> a
p (GarbageStatementOpts -> a) -> GarbageStatementOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageStatementOpts
_goStatement (GarbageOpts -> GarbageStatementOpts)
-> GarbageOpts -> GarbageStatementOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a
-> (GarbageStatementOpts -> a) -> Codec GarbageStatementOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageStatementOpts -> a
p
dfield :: (GarbageStatementOpts -> Double)
-> Key -> Codec GarbageStatementOpts Double
dfield GarbageStatementOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageStatementOpts -> Double
p (GarbageStatementOpts -> Double) -> GarbageStatementOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageStatementOpts
_goStatement (GarbageOpts -> GarbageStatementOpts)
-> GarbageOpts -> GarbageStatementOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageStatementOpts -> Double)
-> Codec GarbageStatementOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageStatementOpts -> Double
p
garbageExprCodec :: TomlCodec GarbageExprOpts
garbageExprCodec :: TomlCodec GarbageExprOpts
garbageExprCodec =
GarbageAttenuationOpts
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts
GarbageExprOpts
(GarbageAttenuationOpts
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts GarbageAttenuationOpts
-> Codec
GarbageExprOpts
(CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec GarbageAttenuationOpts
garbageAttenuationCodec Key
"attenuation" TomlCodec GarbageAttenuationOpts
-> (GarbageExprOpts -> GarbageAttenuationOpts)
-> Codec GarbageExprOpts GarbageAttenuationOpts
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageExprOpts -> GarbageAttenuationOpts
_geoAttenuation
Codec
GarbageExprOpts
(CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoItem Key
"item" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoPrimary Key
"primary" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoUnary Key
"op_unary" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoBinary Key
"op_binary" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(Double
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts Double
-> Codec
GarbageExprOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> Double) -> Key -> Codec GarbageExprOpts Double
dfield GarbageExprOpts -> Double
_geoMinTypMax Key
"minTypMax"
Codec
GarbageExprOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts Double
-> Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> Double) -> Key -> Codec GarbageExprOpts Double
dfield GarbageExprOpts -> Double
_geoDimRange Key
"dimRange"
Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoRange Key
"range_kind" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(Double
-> NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts Double
-> Codec
GarbageExprOpts
(NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> Double) -> Key -> Codec GarbageExprOpts Double
dfield GarbageExprOpts -> Double
_geoRangeOffsetPos_Neg Key
"range_offset_pos_or_neg"
Codec
GarbageExprOpts
(NumberProbability
-> NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts NumberProbability
-> Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageExprOpts NumberProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> NumberProbability
_geoConcatenations Key
"concatenations" TomlCodec NumberProbability
numProbCodec
Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts NumberProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageExprOpts NumberProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> NumberProbability
_geoSysFunArgs Key
"sysFunArgs" TomlCodec NumberProbability
numProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoLiteralWidth Key
"literal_width" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts Double
-> Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> Double) -> Key -> Codec GarbageExprOpts Double
dfield GarbageExprOpts -> Double
_geoLiteralSigned Key
"literal_signed"
Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts NumberProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageExprOpts NumberProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> NumberProbability
_geoStringCharacters Key
"string_characters" TomlCodec NumberProbability
numProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoStringCharacter Key
"string_character" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(Double
-> CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts Double
-> Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> Double) -> Key -> Codec GarbageExprOpts Double
dfield GarbageExprOpts -> Double
_geoFixed_Floating Key
"fixed_or_float"
Codec
GarbageExprOpts
(CategoricalProbability
-> Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoExponentSign Key
"exponentSign" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts Double
-> Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> Double) -> Key -> Codec GarbageExprOpts Double
dfield GarbageExprOpts -> Double
_geoX_Z Key
"X_or_Z"
Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts NumberProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageExprOpts NumberProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> NumberProbability
_geoBinarySymbols Key
"binary_digits" TomlCodec NumberProbability
numProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoBinarySymbol Key
"binary_digit" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts NumberProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageExprOpts NumberProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> NumberProbability
_geoOctalSymbols Key
"octal_digits" TomlCodec NumberProbability
numProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoOctalSymbol Key
"octal_digit" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageExprOpts)
-> Codec GarbageExprOpts NumberProbability
-> Codec
GarbageExprOpts
(CategoricalProbability
-> NumberProbability -> CategoricalProbability -> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageExprOpts NumberProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> NumberProbability
_geoDecimalSymbols Key
"decimal_digits" TomlCodec NumberProbability
numProbCodec
Codec
GarbageExprOpts
(CategoricalProbability
-> NumberProbability -> CategoricalProbability -> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> Codec
GarbageExprOpts
(NumberProbability -> CategoricalProbability -> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoDecimalSymbol Key
"decimal_digit" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageExprOpts
(NumberProbability -> CategoricalProbability -> GarbageExprOpts)
-> Codec GarbageExprOpts NumberProbability
-> Codec
GarbageExprOpts (CategoricalProbability -> GarbageExprOpts)
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageExprOpts NumberProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> NumberProbability
_geoHexadecimalSymbols Key
"hex_digits" TomlCodec NumberProbability
numProbCodec
Codec GarbageExprOpts (CategoricalProbability -> GarbageExprOpts)
-> Codec GarbageExprOpts CategoricalProbability
-> TomlCodec GarbageExprOpts
forall a b.
Codec GarbageExprOpts (a -> b)
-> Codec GarbageExprOpts a -> Codec GarbageExprOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageExprOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageExprOpts CategoricalProbability
forall {a}.
(GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> CategoricalProbability
_geoHexadecimalSymbol Key
"hex_digit" TomlCodec CategoricalProbability
catProbCodec
where
tfield :: (GarbageExprOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageExprOpts a
tfield GarbageExprOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageExprOpts -> a
p (GarbageExprOpts -> a) -> GarbageExprOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageExprOpts
_goExpr (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> GarbageExprOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a -> (GarbageExprOpts -> a) -> Codec GarbageExprOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageExprOpts -> a
p
dfield :: (GarbageExprOpts -> Double) -> Key -> Codec GarbageExprOpts Double
dfield GarbageExprOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageExprOpts -> Double
p (GarbageExprOpts -> Double) -> GarbageExprOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageExprOpts
_goExpr (GarbageOpts -> GarbageExprOpts) -> GarbageOpts -> GarbageExprOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageExprOpts -> Double) -> Codec GarbageExprOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageExprOpts -> Double
p
garbageIdentifierCodec :: TomlCodec GarbageIdentifierOpts
garbageIdentifierCodec :: TomlCodec GarbageIdentifierOpts
garbageIdentifierCodec =
Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts
GarbageIdentifierOpts
(Double
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
-> Codec GarbageIdentifierOpts Double
-> Codec
GarbageIdentifierOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (GarbageIdentifierOpts -> Double)
-> Key -> Codec GarbageIdentifierOpts Double
dfield GarbageIdentifierOpts -> Double
_gioEscaped_Simple Key
"escaped_or_simple"
Codec
GarbageIdentifierOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
-> Codec GarbageIdentifierOpts NumberProbability
-> Codec
GarbageIdentifierOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
forall a b.
Codec GarbageIdentifierOpts (a -> b)
-> Codec GarbageIdentifierOpts a -> Codec GarbageIdentifierOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageIdentifierOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageIdentifierOpts NumberProbability
forall {a}.
(GarbageIdentifierOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageIdentifierOpts a
tfield GarbageIdentifierOpts -> NumberProbability
_gioSimpleLetters Key
"simple_length" TomlCodec NumberProbability
numProbCodec
Codec
GarbageIdentifierOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
-> Codec GarbageIdentifierOpts CategoricalProbability
-> Codec
GarbageIdentifierOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
forall a b.
Codec GarbageIdentifierOpts (a -> b)
-> Codec GarbageIdentifierOpts a -> Codec GarbageIdentifierOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageIdentifierOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageIdentifierOpts CategoricalProbability
forall {a}.
(GarbageIdentifierOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageIdentifierOpts a
tfield GarbageIdentifierOpts -> CategoricalProbability
_gioSimpleLetter Key
"simple_letter" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageIdentifierOpts
(NumberProbability
-> CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
-> Codec GarbageIdentifierOpts NumberProbability
-> Codec
GarbageIdentifierOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
forall a b.
Codec GarbageIdentifierOpts (a -> b)
-> Codec GarbageIdentifierOpts a -> Codec GarbageIdentifierOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageIdentifierOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageIdentifierOpts NumberProbability
forall {a}.
(GarbageIdentifierOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageIdentifierOpts a
tfield GarbageIdentifierOpts -> NumberProbability
_gioEscapedLetters Key
"escaped_length" TomlCodec NumberProbability
numProbCodec
Codec
GarbageIdentifierOpts
(CategoricalProbability
-> NumberProbability
-> CategoricalProbability
-> GarbageIdentifierOpts)
-> Codec GarbageIdentifierOpts CategoricalProbability
-> Codec
GarbageIdentifierOpts
(NumberProbability
-> CategoricalProbability -> GarbageIdentifierOpts)
forall a b.
Codec GarbageIdentifierOpts (a -> b)
-> Codec GarbageIdentifierOpts a -> Codec GarbageIdentifierOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageIdentifierOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageIdentifierOpts CategoricalProbability
forall {a}.
(GarbageIdentifierOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageIdentifierOpts a
tfield GarbageIdentifierOpts -> CategoricalProbability
_gioEscapedLetter Key
"escaped_letter" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageIdentifierOpts
(NumberProbability
-> CategoricalProbability -> GarbageIdentifierOpts)
-> Codec GarbageIdentifierOpts NumberProbability
-> Codec
GarbageIdentifierOpts
(CategoricalProbability -> GarbageIdentifierOpts)
forall a b.
Codec GarbageIdentifierOpts (a -> b)
-> Codec GarbageIdentifierOpts a -> Codec GarbageIdentifierOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageIdentifierOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageIdentifierOpts NumberProbability
forall {a}.
(GarbageIdentifierOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageIdentifierOpts a
tfield GarbageIdentifierOpts -> NumberProbability
_gioSystemLetters Key
"system_length" TomlCodec NumberProbability
numProbCodec
Codec
GarbageIdentifierOpts
(CategoricalProbability -> GarbageIdentifierOpts)
-> Codec GarbageIdentifierOpts CategoricalProbability
-> TomlCodec GarbageIdentifierOpts
forall a b.
Codec GarbageIdentifierOpts (a -> b)
-> Codec GarbageIdentifierOpts a -> Codec GarbageIdentifierOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageIdentifierOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageIdentifierOpts CategoricalProbability
forall {a}.
(GarbageIdentifierOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageIdentifierOpts a
tfield GarbageIdentifierOpts -> CategoricalProbability
_gioSystemFirstLetter Key
"system_first_letter" TomlCodec CategoricalProbability
catProbCodec
where
tfield :: (GarbageIdentifierOpts -> a)
-> Key -> TomlCodec a -> Codec GarbageIdentifierOpts a
tfield GarbageIdentifierOpts -> a
p Key
n TomlCodec a
c =
a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageIdentifierOpts -> a
p (GarbageIdentifierOpts -> a) -> GarbageIdentifierOpts -> a
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageIdentifierOpts
_goIdentifier (GarbageOpts -> GarbageIdentifierOpts)
-> GarbageOpts -> GarbageIdentifierOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a
-> (GarbageIdentifierOpts -> a) -> Codec GarbageIdentifierOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageIdentifierOpts -> a
p
dfield :: (GarbageIdentifierOpts -> Double)
-> Key -> Codec GarbageIdentifierOpts Double
dfield GarbageIdentifierOpts -> Double
p Key
n =
Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageIdentifierOpts -> Double
p (GarbageIdentifierOpts -> Double)
-> GarbageIdentifierOpts -> Double
forall a b. (a -> b) -> a -> b
$ GarbageOpts -> GarbageIdentifierOpts
_goIdentifier (GarbageOpts -> GarbageIdentifierOpts)
-> GarbageOpts -> GarbageIdentifierOpts
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageIdentifierOpts -> Double)
-> Codec GarbageIdentifierOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageIdentifierOpts -> Double
p
garbageCodec :: TomlCodec GarbageOpts
garbageCodec :: TomlCodec GarbageOpts
garbageCodec =
Maybe (Vector Word32)
-> GarbageConfigOpts
-> GarbagePrimitiveOpts
-> GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts
GarbageOpts
(Maybe (Vector Word32)
-> GarbageConfigOpts
-> GarbagePrimitiveOpts
-> GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts (Maybe (Vector Word32))
-> Codec
GarbageOpts
(GarbageConfigOpts
-> GarbagePrimitiveOpts
-> GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TomlCodec (Vector Word32) -> TomlCodec (Maybe (Vector Word32))
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec (Vector Word32)
forall a. (Show a, Read a) => Key -> TomlCodec a
Toml.read Key
"seed") TomlCodec (Maybe (Vector Word32))
-> (GarbageOpts -> Maybe (Vector Word32))
-> Codec GarbageOpts (Maybe (Vector Word32))
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageOpts -> Maybe (Vector Word32)
_goSeed
Codec
GarbageOpts
(GarbageConfigOpts
-> GarbagePrimitiveOpts
-> GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageConfigOpts
-> Codec
GarbageOpts
(GarbagePrimitiveOpts
-> GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageConfigOpts)
-> Key
-> TomlCodec GarbageConfigOpts
-> Codec GarbageOpts GarbageConfigOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageConfigOpts
_goConfig Key
"config" TomlCodec GarbageConfigOpts
garbageConfigCodec
Codec
GarbageOpts
(GarbagePrimitiveOpts
-> GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbagePrimitiveOpts
-> Codec
GarbageOpts
(GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbagePrimitiveOpts)
-> Key
-> TomlCodec GarbagePrimitiveOpts
-> Codec GarbageOpts GarbagePrimitiveOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbagePrimitiveOpts
_goPrimitive Key
"primitive" TomlCodec GarbagePrimitiveOpts
garbagePrimitiveCodec
Codec
GarbageOpts
(GarbageModuleOpts
-> GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageModuleOpts
-> Codec
GarbageOpts
(GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageModuleOpts)
-> Key
-> TomlCodec GarbageModuleOpts
-> Codec GarbageOpts GarbageModuleOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageModuleOpts
_goModule Key
"module" TomlCodec GarbageModuleOpts
garbageModuleCodec
Codec
GarbageOpts
(GarbageSpecifyOpts
-> GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageSpecifyOpts
-> Codec
GarbageOpts
(GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageSpecifyOpts)
-> Key
-> TomlCodec GarbageSpecifyOpts
-> Codec GarbageOpts GarbageSpecifyOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageSpecifyOpts
_goSpecify Key
"specify" TomlCodec GarbageSpecifyOpts
garbageSpecifyCodec
Codec
GarbageOpts
(GarbageGenerateOpts
-> GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageGenerateOpts
-> Codec
GarbageOpts
(GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageGenerateOpts)
-> Key
-> TomlCodec GarbageGenerateOpts
-> Codec GarbageOpts GarbageGenerateOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageGenerateOpts
_goGenerate Key
"generate" TomlCodec GarbageGenerateOpts
garbageGenerateCodec
Codec
GarbageOpts
(GarbageTypeOpts
-> GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageTypeOpts
-> Codec
GarbageOpts
(GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageTypeOpts)
-> Key
-> TomlCodec GarbageTypeOpts
-> Codec GarbageOpts GarbageTypeOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageTypeOpts
_goType Key
"type" TomlCodec GarbageTypeOpts
garbageTypeCodec
Codec
GarbageOpts
(GarbageStatementOpts
-> GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageStatementOpts
-> Codec
GarbageOpts
(GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageStatementOpts)
-> Key
-> TomlCodec GarbageStatementOpts
-> Codec GarbageOpts GarbageStatementOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageStatementOpts
_goStatement Key
"statement" TomlCodec GarbageStatementOpts
garbageStatementCodec
Codec
GarbageOpts
(GarbageExprOpts
-> GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageExprOpts
-> Codec
GarbageOpts
(GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageExprOpts)
-> Key
-> TomlCodec GarbageExprOpts
-> Codec GarbageOpts GarbageExprOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageExprOpts
_goExpr Key
"expr" TomlCodec GarbageExprOpts
garbageExprCodec
Codec
GarbageOpts
(GarbageIdentifierOpts
-> CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts GarbageIdentifierOpts
-> Codec
GarbageOpts
(CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> GarbageIdentifierOpts)
-> Key
-> TomlCodec GarbageIdentifierOpts
-> Codec GarbageOpts GarbageIdentifierOpts
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> GarbageIdentifierOpts
_goIdentifier Key
"identifier" TomlCodec GarbageIdentifierOpts
garbageIdentifierCodec
Codec
GarbageOpts
(CategoricalProbability
-> NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts CategoricalProbability
-> Codec
GarbageOpts
(NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageOpts CategoricalProbability
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> CategoricalProbability
_goDriveStrength Key
"driveStrength" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageOpts
(NumberProbability
-> Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts NumberProbability
-> Codec
GarbageOpts
(Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageOpts NumberProbability
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> NumberProbability
_goLValues Key
"lvalue_items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageOpts
(Double
-> NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts Double
-> Codec
GarbageOpts
(NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double) -> Key -> Codec GarbageOpts Double
dfield GarbageOpts -> Double
_goOptionalLValue Key
"lvalue_optional"
Codec
GarbageOpts
(NumberProbability
-> Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts NumberProbability
-> Codec
GarbageOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageOpts NumberProbability
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> NumberProbability
_goAttributes Key
"attribute_items" TomlCodec NumberProbability
numProbCodec
Codec
GarbageOpts
(Double
-> CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts Double
-> Codec
GarbageOpts
(CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double) -> Key -> Codec GarbageOpts Double
dfield GarbageOpts -> Double
_goAttributeOptionalValue Key
"attribute_optional_value"
Codec
GarbageOpts
(CategoricalProbability
-> CategoricalProbability
-> NumberProbability
-> Double
-> GarbageOpts)
-> Codec GarbageOpts CategoricalProbability
-> Codec
GarbageOpts
(CategoricalProbability
-> NumberProbability -> Double -> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageOpts CategoricalProbability
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> CategoricalProbability
_goDelay Key
"delay_items" TomlCodec CategoricalProbability
catProbCodec
Codec
GarbageOpts
(CategoricalProbability
-> NumberProbability -> Double -> GarbageOpts)
-> Codec GarbageOpts CategoricalProbability
-> Codec GarbageOpts (NumberProbability -> Double -> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> CategoricalProbability)
-> Key
-> TomlCodec CategoricalProbability
-> Codec GarbageOpts CategoricalProbability
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> CategoricalProbability
_goIntRealIdent Key
"delay_base" TomlCodec CategoricalProbability
catProbCodec
Codec GarbageOpts (NumberProbability -> Double -> GarbageOpts)
-> Codec GarbageOpts NumberProbability
-> Codec GarbageOpts (Double -> GarbageOpts)
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> NumberProbability)
-> Key
-> TomlCodec NumberProbability
-> Codec GarbageOpts NumberProbability
forall {a}.
(GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> NumberProbability
_goPathDepth Key
"path_depth" TomlCodec NumberProbability
numProbCodec
Codec GarbageOpts (Double -> GarbageOpts)
-> Codec GarbageOpts Double -> TomlCodec GarbageOpts
forall a b.
Codec GarbageOpts (a -> b)
-> Codec GarbageOpts a -> Codec GarbageOpts b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (GarbageOpts -> Double) -> Key -> Codec GarbageOpts Double
dfield GarbageOpts -> Double
_goBareMinTypMax Key
"parameter_mintypmax_or_single"
where
tfield :: (GarbageOpts -> a) -> Key -> TomlCodec a -> Codec GarbageOpts a
tfield GarbageOpts -> a
p Key
n TomlCodec a
c = a -> TomlCodec a -> TomlCodec a
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageOpts -> a
p (GarbageOpts -> a) -> GarbageOpts -> a
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (TomlCodec a -> Key -> TomlCodec a
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec a
c Key
n) TomlCodec a -> (GarbageOpts -> a) -> Codec GarbageOpts a
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageOpts -> a
p
dfield :: (GarbageOpts -> Double) -> Key -> Codec GarbageOpts Double
dfield GarbageOpts -> Double
p Key
n = Double -> TomlCodec Double -> TomlCodec Double
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue (GarbageOpts -> Double
p (GarbageOpts -> Double) -> GarbageOpts -> Double
forall a b. (a -> b) -> a -> b
$ Config -> GarbageOpts
_configGarbageGenerator Config
defaultConfig) (Key -> TomlCodec Double
Toml.double Key
n) TomlCodec Double
-> (GarbageOpts -> Double) -> Codec GarbageOpts Double
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= GarbageOpts -> Double
p
simulator :: TomlCodec SimDescription
simulator :: TomlCodec SimDescription
simulator = (SimDescription -> Text)
-> (Text -> Either Text SimDescription)
-> Key
-> TomlCodec SimDescription
forall a.
(a -> Text) -> (Text -> Either Text a) -> Key -> TomlCodec a
Toml.textBy SimDescription -> Text
pprint Text -> Either Text SimDescription
parseIcarus Key
"name"
where
parseIcarus :: Text -> Either Text SimDescription
parseIcarus i :: Text
i@Text
"icarus" = SimDescription -> Either Text SimDescription
forall a b. b -> Either a b
Right (SimDescription -> Either Text SimDescription)
-> SimDescription -> Either Text SimDescription
forall a b. (a -> b) -> a -> b
$ Text -> SimDescription
SimDescription Text
i
parseIcarus Text
s = Text -> Either Text SimDescription
forall a b. a -> Either a b
Left (Text -> Either Text SimDescription)
-> Text -> Either Text SimDescription
forall a b. (a -> b) -> a -> b
$ Text
"Could not match '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' with a simulator."
pprint :: SimDescription -> Text
pprint (SimDescription Text
a) = Text
a
synthesiser :: TomlCodec SynthDescription
synthesiser :: TomlCodec SynthDescription
synthesiser =
Text -> Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription
SynthDescription
(Text
-> Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription)
-> Codec SynthDescription Text
-> Codec
SynthDescription
(Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> TomlCodec Text
Toml.text Key
"name"
TomlCodec Text
-> (SynthDescription -> Text) -> Codec SynthDescription Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= SynthDescription -> Text
synthName
Codec
SynthDescription
(Maybe Text -> Maybe Text -> Maybe Text -> SynthDescription)
-> Codec SynthDescription (Maybe Text)
-> Codec
SynthDescription (Maybe Text -> Maybe Text -> SynthDescription)
forall a b.
Codec SynthDescription (a -> b)
-> Codec SynthDescription a -> Codec SynthDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec Text -> TomlCodec (Maybe Text)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Text
Toml.text Key
"bin")
TomlCodec (Maybe Text)
-> (SynthDescription -> Maybe Text)
-> Codec SynthDescription (Maybe Text)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= SynthDescription -> Maybe Text
synthBin
Codec
SynthDescription (Maybe Text -> Maybe Text -> SynthDescription)
-> Codec SynthDescription (Maybe Text)
-> Codec SynthDescription (Maybe Text -> SynthDescription)
forall a b.
Codec SynthDescription (a -> b)
-> Codec SynthDescription a -> Codec SynthDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec Text -> TomlCodec (Maybe Text)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Text
Toml.text Key
"description")
TomlCodec (Maybe Text)
-> (SynthDescription -> Maybe Text)
-> Codec SynthDescription (Maybe Text)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= SynthDescription -> Maybe Text
synthDesc
Codec SynthDescription (Maybe Text -> SynthDescription)
-> Codec SynthDescription (Maybe Text)
-> TomlCodec SynthDescription
forall a b.
Codec SynthDescription (a -> b)
-> Codec SynthDescription a -> Codec SynthDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> TomlCodec Text -> TomlCodec (Maybe Text)
forall a. TomlCodec a -> TomlCodec (Maybe a)
Toml.dioptional (Key -> TomlCodec Text
Toml.text Key
"output")
TomlCodec (Maybe Text)
-> (SynthDescription -> Maybe Text)
-> Codec SynthDescription (Maybe Text)
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= SynthDescription -> Maybe Text
synthOut
emiCodec :: TomlCodec ConfEMI
emiCodec :: TomlCodec ConfEMI
emiCodec =
Int -> Int -> ConfEMI
ConfEMI
(Int -> Int -> ConfEMI)
-> Codec ConfEMI Int -> Codec ConfEMI (Int -> ConfEMI)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting Int Config Int -> Int
forall s a. s -> Getting a s a -> a
^. (ConfEMI -> Const Int ConfEMI) -> Config -> Const Int Config
Lens' Config ConfEMI
configEMI ((ConfEMI -> Const Int ConfEMI) -> Config -> Const Int Config)
-> ((Int -> Const Int Int) -> ConfEMI -> Const Int ConfEMI)
-> Getting Int Config Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Const Int Int) -> ConfEMI -> Const Int ConfEMI
Lens' ConfEMI Int
confEMIGenerateProb)
(Key -> TomlCodec Int
Toml.int Key
"generate_prob")
TomlCodec Int -> (ConfEMI -> Int) -> Codec ConfEMI Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfEMI -> Int
_confEMIGenerateProb
Codec ConfEMI (Int -> ConfEMI)
-> Codec ConfEMI Int -> TomlCodec ConfEMI
forall a b.
Codec ConfEMI (a -> b) -> Codec ConfEMI a -> Codec ConfEMI b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Int -> TomlCodec Int -> TomlCodec Int
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting Int Config Int -> Int
forall s a. s -> Getting a s a -> a
^. (ConfEMI -> Const Int ConfEMI) -> Config -> Const Int Config
Lens' Config ConfEMI
configEMI ((ConfEMI -> Const Int ConfEMI) -> Config -> Const Int Config)
-> ((Int -> Const Int Int) -> ConfEMI -> Const Int ConfEMI)
-> Getting Int Config Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Const Int Int) -> ConfEMI -> Const Int ConfEMI
Lens' ConfEMI Int
confEMINoGenerateProb)
(Key -> TomlCodec Int
Toml.int Key
"nogenerate_prob")
TomlCodec Int -> (ConfEMI -> Int) -> Codec ConfEMI Int
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= ConfEMI -> Int
_confEMINoGenerateProb
infoCodec :: TomlCodec Info
infoCodec :: TomlCodec Info
infoCodec =
Text -> Text -> Info
Info
(Text -> Text -> Info)
-> Codec Info Text -> Codec Info (Text -> Info)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> TomlCodec Text -> TomlCodec Text
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting Text Config Text -> Text
forall s a. s -> Getting a s a -> a
^. (Info -> Const Text Info) -> Config -> Const Text Config
Lens' Config Info
configInfo ((Info -> Const Text Info) -> Config -> Const Text Config)
-> ((Text -> Const Text Text) -> Info -> Const Text Info)
-> Getting Text Config Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Const Text Text) -> Info -> Const Text Info
Lens' Info Text
infoCommit)
(Key -> TomlCodec Text
Toml.text Key
"commit")
TomlCodec Text -> (Info -> Text) -> Codec Info Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Info -> Text
_infoCommit
Codec Info (Text -> Info) -> Codec Info Text -> TomlCodec Info
forall a b. Codec Info (a -> b) -> Codec Info a -> Codec Info b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> TomlCodec Text -> TomlCodec Text
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting Text Config Text -> Text
forall s a. s -> Getting a s a -> a
^. (Info -> Const Text Info) -> Config -> Const Text Config
Lens' Config Info
configInfo ((Info -> Const Text Info) -> Config -> Const Text Config)
-> ((Text -> Const Text Text) -> Info -> Const Text Info)
-> Getting Text Config Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Const Text Text) -> Info -> Const Text Info
Lens' Info Text
infoVersion)
(Key -> TomlCodec Text
Toml.text Key
"version")
TomlCodec Text -> (Info -> Text) -> Codec Info Text
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Info -> Text
_infoVersion
configCodec :: TomlCodec Config
configCodec :: TomlCodec Config
configCodec =
ConfEMI
-> Info
-> Probability
-> ConfProperty
-> GarbageOpts
-> [SimDescription]
-> [SynthDescription]
-> Config
Config
(ConfEMI
-> Info
-> Probability
-> ConfProperty
-> GarbageOpts
-> [SimDescription]
-> [SynthDescription]
-> Config)
-> Codec Config ConfEMI
-> Codec
Config
(Info
-> Probability
-> ConfProperty
-> GarbageOpts
-> [SimDescription]
-> [SynthDescription]
-> Config)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ConfEMI -> TomlCodec ConfEMI -> TomlCodec ConfEMI
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting ConfEMI Config ConfEMI -> ConfEMI
forall s a. s -> Getting a s a -> a
^. Getting ConfEMI Config ConfEMI
Lens' Config ConfEMI
configEMI)
(TomlCodec ConfEMI -> Key -> TomlCodec ConfEMI
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec ConfEMI
emiCodec Key
"emi")
TomlCodec ConfEMI -> (Config -> ConfEMI) -> Codec Config ConfEMI
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Config -> ConfEMI
_configEMI
Codec
Config
(Info
-> Probability
-> ConfProperty
-> GarbageOpts
-> [SimDescription]
-> [SynthDescription]
-> Config)
-> Codec Config Info
-> Codec
Config
(Probability
-> ConfProperty
-> GarbageOpts
-> [SimDescription]
-> [SynthDescription]
-> Config)
forall a b.
Codec Config (a -> b) -> Codec Config a -> Codec Config b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Info -> TomlCodec Info -> TomlCodec Info
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting Info Config Info -> Info
forall s a. s -> Getting a s a -> a
^. Getting Info Config Info
Lens' Config Info
configInfo)
(TomlCodec Info -> Key -> TomlCodec Info
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec Info
infoCodec Key
"info")
TomlCodec Info -> (Config -> Info) -> Codec Config Info
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Config -> Info
_configInfo
Codec
Config
(Probability
-> ConfProperty
-> GarbageOpts
-> [SimDescription]
-> [SynthDescription]
-> Config)
-> Codec Config Probability
-> Codec
Config
(ConfProperty
-> GarbageOpts -> [SimDescription] -> [SynthDescription] -> Config)
forall a b.
Codec Config (a -> b) -> Codec Config a -> Codec Config b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Probability -> TomlCodec Probability -> TomlCodec Probability
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting Probability Config Probability -> Probability
forall s a. s -> Getting a s a -> a
^. Getting Probability Config Probability
Lens' Config Probability
configProbability)
(TomlCodec Probability -> Key -> TomlCodec Probability
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec Probability
probCodec Key
"probability")
TomlCodec Probability
-> (Config -> Probability) -> Codec Config Probability
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Config -> Probability
_configProbability
Codec
Config
(ConfProperty
-> GarbageOpts -> [SimDescription] -> [SynthDescription] -> Config)
-> Codec Config ConfProperty
-> Codec
Config
(GarbageOpts -> [SimDescription] -> [SynthDescription] -> Config)
forall a b.
Codec Config (a -> b) -> Codec Config a -> Codec Config b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ConfProperty -> TomlCodec ConfProperty -> TomlCodec ConfProperty
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting ConfProperty Config ConfProperty -> ConfProperty
forall s a. s -> Getting a s a -> a
^. Getting ConfProperty Config ConfProperty
Lens' Config ConfProperty
configProperty)
(TomlCodec ConfProperty -> Key -> TomlCodec ConfProperty
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec ConfProperty
propCodec Key
"property")
TomlCodec ConfProperty
-> (Config -> ConfProperty) -> Codec Config ConfProperty
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Config -> ConfProperty
_configProperty
Codec
Config
(GarbageOpts -> [SimDescription] -> [SynthDescription] -> Config)
-> Codec Config GarbageOpts
-> Codec Config ([SimDescription] -> [SynthDescription] -> Config)
forall a b.
Codec Config (a -> b) -> Codec Config a -> Codec Config b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> GarbageOpts -> TomlCodec GarbageOpts -> TomlCodec GarbageOpts
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config -> Getting GarbageOpts Config GarbageOpts -> GarbageOpts
forall s a. s -> Getting a s a -> a
^. Getting GarbageOpts Config GarbageOpts
Lens' Config GarbageOpts
configGarbageGenerator)
(TomlCodec GarbageOpts -> Key -> TomlCodec GarbageOpts
forall a. TomlCodec a -> Key -> TomlCodec a
Toml.table TomlCodec GarbageOpts
garbageCodec Key
"invalid_generator")
TomlCodec GarbageOpts
-> (Config -> GarbageOpts) -> Codec Config GarbageOpts
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Config -> GarbageOpts
_configGarbageGenerator
Codec Config ([SimDescription] -> [SynthDescription] -> Config)
-> Codec Config [SimDescription]
-> Codec Config ([SynthDescription] -> Config)
forall a b.
Codec Config (a -> b) -> Codec Config a -> Codec Config b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [SimDescription]
-> TomlCodec [SimDescription] -> TomlCodec [SimDescription]
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config
-> Getting [SimDescription] Config [SimDescription]
-> [SimDescription]
forall s a. s -> Getting a s a -> a
^. Getting [SimDescription] Config [SimDescription]
Lens' Config [SimDescription]
configSimulators)
(TomlCodec SimDescription -> Key -> TomlCodec [SimDescription]
forall a. TomlCodec a -> Key -> TomlCodec [a]
Toml.list TomlCodec SimDescription
simulator Key
"simulator")
TomlCodec [SimDescription]
-> (Config -> [SimDescription]) -> Codec Config [SimDescription]
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Config -> [SimDescription]
_configSimulators
Codec Config ([SynthDescription] -> Config)
-> Codec Config [SynthDescription] -> TomlCodec Config
forall a b.
Codec Config (a -> b) -> Codec Config a -> Codec Config b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [SynthDescription]
-> TomlCodec [SynthDescription] -> TomlCodec [SynthDescription]
forall a. a -> TomlCodec a -> TomlCodec a
defaultValue
(Config
defaultConfig Config
-> Getting [SynthDescription] Config [SynthDescription]
-> [SynthDescription]
forall s a. s -> Getting a s a -> a
^. Getting [SynthDescription] Config [SynthDescription]
Lens' Config [SynthDescription]
configSynthesisers)
(TomlCodec SynthDescription -> Key -> TomlCodec [SynthDescription]
forall a. TomlCodec a -> Key -> TomlCodec [a]
Toml.list TomlCodec SynthDescription
synthesiser Key
"synthesiser")
TomlCodec [SynthDescription]
-> (Config -> [SynthDescription])
-> Codec Config [SynthDescription]
forall field a object.
Codec field a -> (object -> field) -> Codec object a
.= Config -> [SynthDescription]
_configSynthesisers
parseConfigFile :: FilePath -> IO (Either Text Config)
parseConfigFile :: String -> IO (Either Text Config)
parseConfigFile String
fp = do
Either [TomlDecodeError] Config
decoded <- TomlCodec Config -> String -> IO (Either [TomlDecodeError] Config)
forall a (m :: * -> *).
MonadIO m =>
TomlCodec a -> String -> m (Either [TomlDecodeError] a)
Toml.decodeFileExact TomlCodec Config
configCodec String
fp
case Either [TomlDecodeError] Config
decoded of
Right Config
c -> Either Text Config -> IO (Either Text Config)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text Config -> IO (Either Text Config))
-> Either Text Config -> IO (Either Text Config)
forall a b. (a -> b) -> a -> b
$ Config -> Either Text Config
forall a b. b -> Either a b
Right Config
c
Left [TomlDecodeError]
e -> Either Text Config -> IO (Either Text Config)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text Config -> IO (Either Text Config))
-> (Text -> Either Text Config) -> Text -> IO (Either Text Config)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text Config
forall a b. a -> Either a b
Left (Text -> IO (Either Text Config))
-> Text -> IO (Either Text Config)
forall a b. (a -> b) -> a -> b
$ [TomlDecodeError] -> Text
Toml.prettyTomlDecodeErrors [TomlDecodeError]
e
parseConfig :: Text -> Either Text Config
parseConfig :: Text -> Either Text Config
parseConfig Text
t = case TomlCodec Config -> Text -> Either [TomlDecodeError] Config
forall a. TomlCodec a -> Text -> Either [TomlDecodeError] a
Toml.decodeExact TomlCodec Config
configCodec Text
t of
Right Config
c -> Config -> Either Text Config
forall a b. b -> Either a b
Right Config
c
Left [TomlDecodeError]
e -> Text -> Either Text Config
forall a b. a -> Either a b
Left (Text -> Either Text Config) -> Text -> Either Text Config
forall a b. (a -> b) -> a -> b
$ [TomlDecodeError] -> Text
Toml.prettyTomlDecodeErrors [TomlDecodeError]
e
parseConfigFileRelaxed :: FilePath -> IO (Either Text Config)
parseConfigFileRelaxed :: String -> IO (Either Text Config)
parseConfigFileRelaxed String
fp = do
Either [TomlDecodeError] Config
decoded <- TomlCodec Config -> String -> IO (Either [TomlDecodeError] Config)
forall a (m :: * -> *).
MonadIO m =>
TomlCodec a -> String -> m (Either [TomlDecodeError] a)
Toml.decodeFileEither TomlCodec Config
configCodec String
fp
case Either [TomlDecodeError] Config
decoded of
Right Config
c -> Either Text Config -> IO (Either Text Config)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text Config -> IO (Either Text Config))
-> Either Text Config -> IO (Either Text Config)
forall a b. (a -> b) -> a -> b
$ Config -> Either Text Config
forall a b. b -> Either a b
Right Config
c
Left [TomlDecodeError]
e -> Either Text Config -> IO (Either Text Config)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text Config -> IO (Either Text Config))
-> (Text -> Either Text Config) -> Text -> IO (Either Text Config)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text Config
forall a b. a -> Either a b
Left (Text -> IO (Either Text Config))
-> Text -> IO (Either Text Config)
forall a b. (a -> b) -> a -> b
$ [TomlDecodeError] -> Text
Toml.prettyTomlDecodeErrors [TomlDecodeError]
e
parseConfigRelaxed :: Text -> Either Text Config
parseConfigRelaxed :: Text -> Either Text Config
parseConfigRelaxed Text
t = case TomlCodec Config -> Text -> Either [TomlDecodeError] Config
forall a. TomlCodec a -> Text -> Either [TomlDecodeError] a
Toml.decode TomlCodec Config
configCodec Text
t of
Right Config
c -> Config -> Either Text Config
forall a b. b -> Either a b
Right Config
c
Left [TomlDecodeError]
e -> Text -> Either Text Config
forall a b. a -> Either a b
Left (Text -> Either Text Config) -> Text -> Either Text Config
forall a b. (a -> b) -> a -> b
$ [TomlDecodeError] -> Text
Toml.prettyTomlDecodeErrors [TomlDecodeError]
e
encodeConfig :: Config -> Text
encodeConfig :: Config -> Text
encodeConfig = TomlCodec Config -> Config -> Text
forall a. TomlCodec a -> a -> Text
Toml.encode TomlCodec Config
configCodec
encodeConfigFile :: FilePath -> Config -> IO ()
encodeConfigFile :: String -> Config -> IO ()
encodeConfigFile String
f = String -> Text -> IO ()
T.writeFile String
f (Text -> IO ()) -> (Config -> Text) -> Config -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Text
encodeConfig
versionInfo :: String
versionInfo :: String
versionInfo =
String
"Verismith "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
version
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" ("
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> $(gitCommitDate)
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> $(gitHash)
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"