never executed always true always false
    1 {-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
    2 {-# OPTIONS_GHC -fno-cse #-} -- stupid cmdargs
    3 
    4 module Conjure.UI ( UI(..), OutputFormat(..), ui, versionLine ) where
    5 
    6 -- conjure
    7 import Conjure.Prelude
    8 import Conjure.RepositoryVersion ( repositoryVersion )
    9 import Paths_conjure_cp ( version )
   10 
   11 -- base
   12 import Data.Version ( showVersion )
   13 
   14 -- cmdargs
   15 import System.Console.CmdArgs hiding ( Default(..) )
   16 
   17 
   18 data UI
   19     = Modelling
   20         { essence                    :: FilePath            -- essence, mandatory
   21         -- flags related to output
   22         , outputDirectory            :: FilePath
   23         , numberingStart             :: Int
   24         , smartFilenames             :: Bool
   25         , responses                  :: String
   26         , responsesRepresentation    :: String
   27         , estimateNumberOfModels     :: Bool                -- if set Conjure will calculate
   28                                                             -- a lower bound on the number of models,
   29                                                             -- instead of running the usual modelling mode
   30         -- flags related to logging
   31         , logLevel                   :: LogLevel
   32         , verboseTrail               :: Bool
   33         , rewritesTrail              :: Bool
   34         , logRuleFails               :: Bool
   35         , logRuleSuccesses           :: Bool
   36         , logRuleAttempts            :: Bool
   37         , logChoices                 :: Bool
   38         -- flags related to modelling decisions
   39         , portfolio                  :: Maybe Int
   40         , strategyQ                  :: String
   41         , strategyA                  :: String
   42         , representations            :: Maybe String        -- (def: strategyA)
   43         , representationsFinds       :: Maybe String        -- (def: representations)
   44         , representationsGivens      :: Maybe String        -- (def: s)
   45         , representationsAuxiliaries :: Maybe String        -- (def: representations)
   46         , representationsQuantifieds :: Maybe String        -- (def: representations)
   47         , representationsCuts        :: Maybe String        -- (def: representations)
   48         , channelling                :: Bool
   49         , representationLevels       :: Bool                -- (def: True)
   50         , followModel                :: FilePath            -- this is a model to be followed
   51         , seed                       :: Maybe Int
   52         , limitModels                :: Maybe Int
   53         , limitTime                  :: Maybe Int
   54         , savedChoices               :: Maybe FilePath
   55         , outputFormat               :: OutputFormat        -- Essence by default
   56         , lineWidth                  :: Int                 -- 120 by default
   57         -- streamlining
   58         , generateStreamliners       :: String
   59         }
   60     | TranslateParameter
   61         { eprime                     :: FilePath            -- eprime, mandatory
   62         , essenceParam               :: FilePath            -- essence-param, mandatory
   63         , eprimeParam                :: Maybe FilePath      -- eprime-param, optional
   64                                                             -- by default (essenceParam <-.> "eprime-param")
   65         , logLevel                   :: LogLevel
   66         , limitTime                  :: Maybe Int
   67         , outputFormat               :: OutputFormat        -- Essence by default
   68         , lineWidth                  :: Int                 -- 120 by default
   69         }
   70     | TranslateSolution
   71         { eprime                     :: FilePath            -- eprime, mandatory
   72         , essenceParamO              :: Maybe FilePath      -- essence-param, optional
   73         , eprimeSolution             :: FilePath            -- eprime-solution, mandatory
   74         , essenceSolutionO           :: Maybe FilePath      -- essence-solution, optional
   75                                                             -- by default (eprimeSolution <-.> "solution")
   76         , logLevel                   :: LogLevel
   77         , limitTime                  :: Maybe Int
   78         , outputFormat               :: OutputFormat        -- Essence by default
   79         , lineWidth                  :: Int                 -- 120 by default
   80         }
   81     | ValidateSolution
   82         { essence                    :: FilePath            -- essence, mandatory
   83         , essenceParamO              :: Maybe FilePath      -- essence-param, optional
   84         , essenceSolution            :: FilePath            -- essence-solution, mandatory
   85                                                             -- by default (eprimeSolution <-.> "solution")
   86         , logLevel                   :: LogLevel
   87         , limitTime                  :: Maybe Int
   88         , outputFormat               :: OutputFormat        -- Essence by default
   89         , lineWidth                  :: Int                 -- 120 by default
   90         }
   91     | Solve
   92         { essence                    :: FilePath            -- essence, mandatory
   93         , essenceParams              :: [FilePath]
   94         , validateSolutionsOpt       :: Bool
   95         -- flags related to output
   96         , outputDirectory            :: FilePath
   97         , numberingStart             :: Int
   98         , smartFilenames             :: Bool
   99         , responses                  :: String
  100         , responsesRepresentation    :: String
  101         , solutionsInOneFile         :: Bool
  102         , runsolverCPUTimeLimit      :: Maybe Int
  103         , runsolverWallTimeLimit     :: Maybe Int
  104         , runsolverMemoryLimit       :: Maybe Int
  105         -- flags related to logging
  106         , logLevel                   :: LogLevel
  107         , verboseTrail               :: Bool
  108         , rewritesTrail              :: Bool
  109         , logRuleFails               :: Bool
  110         , logRuleSuccesses           :: Bool
  111         , logRuleAttempts            :: Bool
  112         , logChoices                 :: Bool
  113         -- flags related to modelling decisions
  114         , portfolio                  :: Maybe Int
  115         , strategyQ                  :: String
  116         , strategyA                  :: String
  117         , representations            :: Maybe String
  118         , representationsFinds       :: Maybe String
  119         , representationsGivens      :: Maybe String
  120         , representationsAuxiliaries :: Maybe String
  121         , representationsQuantifieds :: Maybe String
  122         , representationsCuts        :: Maybe String
  123         , channelling                :: Bool
  124         , representationLevels       :: Bool                -- (def: True)
  125         , followModel                :: FilePath            -- this is a model to be followed
  126         , seed                       :: Maybe Int
  127         , limitModels                :: Maybe Int
  128         , limitTime                  :: Maybe Int
  129         , useExistingModels          :: [FilePath]          -- [] by default, which means generate models
  130         -- flags for SR and the selected solver
  131         , savilerowOptions           :: [String]
  132         , solverOptions              :: [String]
  133         , solver                     :: String
  134         , graphSolver                :: Bool
  135         , cgroups                    :: Bool
  136         , nbSolutions                :: String              -- a number, or "all". by default 1
  137         , copySolutions              :: Bool
  138         -- output
  139         , outputFormat               :: OutputFormat        -- Essence by default
  140         , lineWidth                  :: Int                 -- 120 by default
  141         -- streamlining
  142         , generateStreamliners       :: String
  143         }
  144     | IDE
  145         { essence                    :: FilePath            -- Optional, will read from stdin if not provided
  146         , logLevel                   :: LogLevel
  147         , limitTime                  :: Maybe Int
  148         , lineWidth                  :: Int                 -- 120 by default
  149         , dumpDeclarations           :: Bool
  150         , dumpRepresentations        :: Bool
  151         }
  152     | Pretty
  153         { essence                    :: FilePath
  154         , normaliseQuantified        :: Bool
  155         , removeUnused               :: Bool
  156         , logLevel                   :: LogLevel
  157         , limitTime                  :: Maybe Int
  158         , outputFormat               :: OutputFormat        -- Essence by default
  159         , lineWidth                  :: Int                 -- 120 by default
  160         }
  161     | Diff
  162         { file1                      :: FilePath
  163         , file2                      :: FilePath
  164         , logLevel                   :: LogLevel
  165         , limitTime                  :: Maybe Int
  166         , outputFormat               :: OutputFormat        -- Essence by default
  167         , lineWidth                  :: Int                 -- 120 by default
  168         }
  169     | TypeCheck
  170         { essence                    :: FilePath
  171         , logLevel                   :: LogLevel
  172         , limitTime                  :: Maybe Int
  173         }
  174     | Split
  175         { essence                    :: FilePath
  176         , outputDirectory            :: FilePath
  177         , logLevel                   :: LogLevel
  178         , limitTime                  :: Maybe Int
  179         , outputFormat               :: OutputFormat        -- Essence by default
  180         , lineWidth                  :: Int                 -- 120 by default
  181         }
  182     | SymmetryDetection
  183         { essence                    :: FilePath
  184         , json                       :: FilePath
  185         , logLevel                   :: LogLevel
  186         , limitTime                  :: Maybe Int
  187         , outputFormat               :: OutputFormat        -- Essence by default
  188         , lineWidth                  :: Int                 -- 120 by default
  189         }
  190     | ParameterGenerator
  191         { essence                    :: FilePath
  192         , minInt                     :: Integer
  193         , maxInt                     :: Integer
  194         , logLevel                   :: LogLevel
  195         , limitTime                  :: Maybe Int
  196         , outputFormat               :: OutputFormat        -- Essence by default
  197         , lineWidth                  :: Int                 -- 120 by default
  198         }
  199     | AutoIG
  200         { essence                    :: FilePath
  201         , outputFilepath             :: FilePath
  202         , generatorToIrace           :: Bool
  203         , removeAux                  :: Bool
  204         , logLevel                   :: LogLevel
  205         , limitTime                  :: Maybe Int
  206         , outputFormat               :: OutputFormat        -- Essence by default
  207         , lineWidth                  :: Int                 -- 120 by default
  208         }
  209     | Boost
  210         { essence                    :: FilePath
  211         , logLevel                   :: LogLevel
  212         , logRuleSuccesses           :: Bool
  213         , limitTime                  :: Maybe Int
  214         , outputFormat               :: OutputFormat        -- Essence by default
  215         , lineWidth                  :: Int                 -- 120 by default
  216         }
  217     | Streamlining
  218         { essence                    :: FilePath
  219         , logLevel                   :: LogLevel
  220         , limitTime                  :: Maybe Int
  221         , outputFormat               :: OutputFormat        -- Essence by default
  222         , lineWidth                  :: Int                 -- 120 by default
  223         }
  224     | LSP
  225         { logLevel                   :: LogLevel
  226         , limitTime                  :: Maybe Int
  227         }
  228     deriving (Eq, Ord, Show, Data, Typeable, Generic)
  229 
  230 instance Serialize UI
  231 instance Hashable  UI
  232 instance ToJSON    UI where toJSON = genericToJSON jsonOptions
  233 instance FromJSON  UI where parseJSON = genericParseJSON jsonOptions
  234 
  235 
  236 data OutputFormat = Plain | Binary | ASTJSON | JSON | JSONStream | MiniZinc
  237     deriving (Eq, Ord, Show, Data, Typeable, Generic)
  238 
  239 instance Serialize OutputFormat
  240 instance Hashable  OutputFormat
  241 instance ToJSON    OutputFormat where toJSON = genericToJSON jsonOptions
  242 instance FromJSON  OutputFormat where parseJSON = genericParseJSON jsonOptions
  243 
  244 instance Default OutputFormat where def = Plain
  245 
  246 
  247 ui :: UI
  248 ui = modes
  249     [ Modelling
  250         { essence
  251             = def
  252             &= typ "ESSENCE_FILE"
  253             &= argPos 0
  254         , outputDirectory
  255             = "conjure-output"
  256             &= typDir
  257             &= name "output-directory"
  258             &= name "o"
  259             &= groupname "Logging & Output"
  260             &= explicit
  261             &= help "Where to save generated models.\n\
  262                     \Default value: 'conjure-output'"
  263         , numberingStart
  264             = 1
  265             &= name "numbering-start"
  266             &= groupname "Logging & Output"
  267             &= explicit
  268             &= help "Starting value for output files.\n\
  269                     \Default value: 1"
  270         , smartFilenames
  271             = False
  272             &= name "smart-filenames"
  273             &= groupname "Logging & Output"
  274             &= explicit
  275             &= help "Use \"smart names\" for models.\n\
  276                     \Directs Conjure to use the answers when producing \
  277                     \a filename and to ignore the order of questions. \
  278                     \Only useful if 'f' is used for questions."
  279         , responses
  280             = ""
  281             &= name "responses"
  282             &= groupname "Model generation"
  283             &= explicit
  284             &= help "A comma separated list of integers.\n\
  285                     \If provided, these will be used as the answers during \
  286                     \interactive model generation instead of prompting the user."
  287         , responsesRepresentation
  288             = ""
  289             &= name "responses-representation"
  290             &= groupname "Model generation"
  291             &= explicit
  292             &= help "A comma separated list of variable name : integer pairs.\n\
  293                     \If provided, these will be used as the answers during \
  294                     \interactive model generation instead of prompting the user \
  295                     \for the variable representation questions.\n\
  296                     \See --dump-representations for a list of available representation options."
  297         , estimateNumberOfModels
  298             = False
  299             &= name "estimate-number-of-models"
  300             &= groupname "Model generation"
  301             &= explicit
  302             &= help "Calculate (a lower bound on) the number of models, \
  303                     \instead of running the usual modelling mode."
  304         , logLevel
  305             = def
  306             &= name "log-level"
  307             &= groupname "Logging & Output"
  308             &= explicit
  309             &= help "Log level."
  310         , verboseTrail
  311             = False
  312             &= name "verbose-trail"
  313             &= groupname "Logging & Output"
  314             &= explicit
  315             &= help "Generate verbose trails."
  316         , rewritesTrail
  317             = False
  318             &= name "rewrites-trail"
  319             &= groupname "Logging & Output"
  320             &= explicit
  321             &= help "Generate trails about the applied rewritings."
  322         , logRuleFails
  323             = False
  324             &= name "log-rule-fails"
  325             &= groupname "Logging & Output"
  326             &= explicit
  327             &= help "Generate logs for rule failures. (Caution: can be a lot!)"
  328         , logRuleSuccesses
  329             = False
  330             &= name "log-rule-successes"
  331             &= groupname "Logging & Output"
  332             &= explicit
  333             &= help "Generate logs for rule applications."
  334         , logRuleAttempts
  335             = False
  336             &= name "log-rule-attempts"
  337             &= groupname "Logging & Output"
  338             &= explicit
  339             &= help "Generate logs for rule attempts. (Caution: can be a lot!)"
  340         , logChoices
  341             = False
  342             &= name "log-choices"
  343             &= groupname "Logging & Output"
  344             &= explicit
  345             &= help "Store the choices in a way that can be reused by -al"
  346         , portfolio
  347             = Nothing
  348             &= typ "PORTFOLIO"
  349             &= name "portfolio"
  350             &= groupname "Model generation"
  351             &= explicit
  352             &= help "Portfolio size. When it is set to N, Conjure will try to generate up to N models."
  353         , strategyQ
  354             = "f"
  355             &= typ "STRATEGY"
  356             &= name "strategy-q"
  357             &= name "q"
  358             &= groupname "Model generation"
  359             &= explicit
  360             &= help "Strategy for selecting the next question to answer. \
  361                     \Options: f (for first), i (for interactive), r (for random), x (for all). \
  362                     \Prepend a (for auto) to automatically skip \
  363                     \when there is only one option at any point.\n\
  364                     \Default value: f"
  365         , strategyA
  366             = "ai"
  367             &= typ "STRATEGY"
  368             &= name "strategy-a"
  369             &= name "a"
  370             &= groupname "Model generation"
  371             &= explicit
  372             &= help "Strategy for selecting an answer. Same options as strategy-q.\n\
  373                     \ c picks the most 'compact' option \
  374                     \at every decision point.\n\
  375                     \ s picks the 'sparsest' option \
  376                     \at every decision point: \
  377                     \useful for --representations-givens\n\
  378                     \Default value: ai"
  379         , representations
  380             = Nothing
  381             &= typ "STRATEGY"
  382             &= name "representations"
  383             &= groupname "Model generation"
  384             &= explicit
  385             &= help "Strategy for choosing a representation.\n\
  386                     \Default value: same as --strategy-a"
  387         , representationsFinds
  388             = Nothing
  389             &= typ "STRATEGY"
  390             &= name "representations-finds"
  391             &= groupname "Model generation"
  392             &= explicit
  393             &= help "Strategy for choosing a representation for a decision variable.\n\
  394                     \Default value: same as --representations"
  395         , representationsGivens
  396             = Nothing
  397             &= typ "STRATEGY"
  398             &= name "representations-givens"
  399             &= groupname "Model generation"
  400             &= explicit
  401             &= help "Strategy for choosing a representation for a parameter.\n\
  402                     \Default value: s (for sparse)"
  403         , representationsAuxiliaries
  404             = Nothing
  405             &= typ "STRATEGY"
  406             &= name "representations-auxiliaries"
  407             &= groupname "Model generation"
  408             &= explicit
  409             &= help "Strategy for choosing a representation for an auxiliary variable.\n\
  410                     \Default value: same as --representations"
  411         , representationsQuantifieds
  412             = Nothing
  413             &= typ "STRATEGY"
  414             &= name "representations-quantifieds"
  415             &= groupname "Model generation"
  416             &= explicit
  417             &= help "Strategy for choosing a representation for a quantified variable.\n\
  418                     \Default value: same as --representations"
  419         , representationsCuts
  420             = Nothing
  421             &= typ "STRATEGY"
  422             &= name "representations-cuts"
  423             &= groupname "Model generation"
  424             &= explicit
  425             &= help "Strategy for choosing a representation for cuts in 'branching on'.\n\
  426                     \Default value: same as --representations"
  427         , channelling
  428             = True
  429             &= name "channelling"
  430             &= groupname "Model generation"
  431             &= explicit
  432             &= help "Whether to produce channelled models \
  433                     \(true by default).\n"
  434         , representationLevels
  435             = True
  436             &= name "representation-levels"
  437             &= groupname "Model generation"
  438             &= explicit
  439             &= help "Whether to use built-in precedence levels when choosing representations. \
  440                     \Used to cut down the number of generated models.\n\
  441                     \Default: true"
  442         , followModel
  443             = ""
  444             &= name "follow-model"
  445             &= groupname "Model generation"
  446             &= explicit
  447             &= help "Provide a Conjure-generated Essence Prime model to be used as a guide during model generation. \
  448                     \Conjure will try to imitate the modelling decisions from this file."
  449         , seed
  450             = Nothing
  451             &= name "seed"
  452             &= groupname "Model generation"
  453             &= explicit
  454             &= help "Random number generator seed."
  455         , limitModels
  456             = Nothing
  457             &= name "limit-models"
  458             &= groupname "Model generation"
  459             &= explicit
  460             &= help "Maximum number of models to generate."
  461         , limitTime
  462             = Nothing
  463             &= name "limit-time"
  464             &= groupname "General"
  465             &= explicit
  466             &= help "Limit in seconds of real time."
  467         , savedChoices
  468             = def
  469             &= typFile
  470             &= name "choices"
  471             &= groupname "Model generation"
  472             &= explicit
  473             &= help "Choices to use for -al, \
  474                      \either an eprime file (created by --log-choices), or a json file."
  475         , outputFormat
  476             = def
  477             &= name "output-format"
  478             &= groupname "Logging & Output"
  479             &= explicit
  480             &= typ "FORMAT"
  481             &= help "Format to use for output. All output formats can also be used for input.\n\
  482                     \    plain: default\n\
  483                     \    binary: a binary encoding\n\
  484                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
  485                     \    json: a simplified JSON format, only used for parameters and solutions\n\
  486                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
  487                     \    minizinc: minizinc format for data files, only used for solutions\n"
  488         , lineWidth
  489             = 120
  490             &= name "line-width"
  491             &= groupname "Logging & Output"
  492             &= explicit
  493             &= help "Line width for pretty printing.\nDefault: 120"
  494         , generateStreamliners
  495             = ""
  496             &= name "generate-streamliners"
  497             &= groupname "Streamlining"
  498             &= explicit
  499             &= help "A comma separated list of integers.\n\
  500                     \If provided, the streamlining constraints that correspond to the given integers will be generated.\n\
  501                     \Run \"conjure streamlining ESSENCE_FILE\" to generate a list of all applicable streamliners."
  502         }   &= name "modelling"
  503             &= explicit
  504             &= help "The main act. Given a problem specification in Essence, \
  505                     \produce constraint programming models in Essence'."
  506             &= auto
  507     , TranslateParameter
  508         { eprime
  509             = def
  510             &= typ "ESSENCE_FILE"
  511             &= name "eprime"
  512             &= explicit
  513             &= help "An Essence' model generated by Conjure."
  514         , essenceParam
  515             = def
  516             &= typFile
  517             &= name "essence-param"
  518             &= explicit
  519             &= help "An Essence parameter for the original problem specification."
  520         , eprimeParam
  521             = def
  522             &= typFile
  523             &= name "eprime-param"
  524             &= explicit
  525             &= help "An Essence' parameter matching the Essence' model.\n\
  526                     \Default is 'foo.eprime-param' \
  527                     \if the Essence parameter file is named 'foo.param'."
  528         , logLevel
  529             = def
  530             &= name "log-level"
  531             &= groupname "Logging & Output"
  532             &= explicit
  533             &= help "Log level."
  534         , limitTime
  535             = Nothing
  536             &= name "limit-time"
  537             &= groupname "General"
  538             &= explicit
  539             &= help "Limit in seconds of real time."
  540         , outputFormat
  541             = def
  542             &= name "output-format"
  543             &= groupname "Logging & Output"
  544             &= explicit
  545             &= typ "FORMAT"
  546             &= help "Format to use for output. All output formats can also be used for input.\n\
  547                     \    plain: default\n\
  548                     \    binary: a binary encoding\n\
  549                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
  550                     \    json: a simplified JSON format, only used for parameters and solutions\n\
  551                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
  552                     \    minizinc: minizinc format for data files, only used for solutions\n"
  553         , lineWidth
  554             = 120
  555             &= name "line-width"
  556             &= groupname "Logging & Output"
  557             &= explicit
  558             &= help "Line width for pretty printing.\nDefault: 120"
  559         }   &= name "translate-parameter"
  560             &= explicit
  561             &= help "Refinement of Essence parameter files for a \
  562                     \particular Essence' model.\n\
  563                     \The model needs to be generated by Conjure."
  564     , TranslateSolution
  565         { eprime
  566             = def
  567             &= typFile
  568             &= name "eprime"
  569             &= explicit
  570             &= help "An Essence' model generated by Conjure.\n\
  571                      \Mandatory."
  572         , essenceParamO
  573             = def
  574             &= typFile
  575             &= name "essence-param"
  576             &= explicit
  577             &= help "An Essence parameter for the original problem specification.\n\
  578                      \Mandatory."
  579         , eprimeSolution
  580             = def
  581             &= typFile
  582             &= name "eprime-solution"
  583             &= explicit
  584             &= help "An Essence' solution for the corresponding Essence' model."
  585         , essenceSolutionO
  586             = def
  587             &= typFile
  588             &= name "essence-solution"
  589             &= explicit
  590             &= help "An Essence solution for the original problem specification.\n\
  591                     \By default, its value is the value of --eprime-solution \
  592                     \with extensions replaced by '.solution'."
  593         , logLevel
  594             = def
  595             &= name "log-level"
  596             &= groupname "Logging & Output"
  597             &= explicit
  598             &= help "Log level."
  599         , limitTime
  600             = Nothing
  601             &= name "limit-time"
  602             &= groupname "General"
  603             &= explicit
  604             &= help "Limit in seconds of real time."
  605         , outputFormat
  606             = def
  607             &= name "output-format"
  608             &= groupname "Logging & Output"
  609             &= explicit
  610             &= typ "FORMAT"
  611             &= help "Format to use for output. All output formats can also be used for input.\n\
  612                     \    plain: default\n\
  613                     \    binary: a binary encoding\n\
  614                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
  615                     \    json: a simplified JSON format, only used for parameters and solutions\n\
  616                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
  617                     \    minizinc: minizinc format for data files, only used for solutions\n"
  618         , lineWidth
  619             = 120
  620             &= name "line-width"
  621             &= groupname "Logging & Output"
  622             &= explicit
  623             &= help "Line width for pretty printing.\nDefault: 120"
  624         }   &= name "translate-solution"
  625             &= explicit
  626             &= help "Translation of solutions back to Essence."
  627     , ValidateSolution
  628         { essence
  629             = def
  630             &= typ "ESSENCE_FILE"
  631             &= name "essence"
  632             &= explicit
  633             &= help "Problem specification in Essence."
  634         , essenceParamO
  635             = def
  636             &= typFile
  637             &= name "param"
  638             &= explicit
  639             &= help "Essence parameter file."
  640         , essenceSolution
  641             = def
  642             &= typFile
  643             &= name "solution"
  644             &= explicit
  645             &= help "Essence solution."
  646         , logLevel
  647             = def
  648             &= name "log-level"
  649             &= groupname "Logging & Output"
  650             &= explicit
  651             &= help "Log level."
  652         , limitTime
  653             = Nothing
  654             &= name "limit-time"
  655             &= groupname "General"
  656             &= explicit
  657             &= help "Limit in seconds of real time."
  658         , outputFormat
  659             = def
  660             &= name "output-format"
  661             &= groupname "Logging & Output"
  662             &= explicit
  663             &= typ "FORMAT"
  664             &= help "Format to use for output. All output formats can also be used for input.\n\
  665                     \    plain: default\n\
  666                     \    binary: a binary encoding\n\
  667                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
  668                     \    json: a simplified JSON format, only used for parameters and solutions\n\
  669                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
  670                     \    minizinc: minizinc format for data files, only used for solutions\n"
  671         , lineWidth
  672             = 120
  673             &= name "line-width"
  674             &= groupname "Logging & Output"
  675             &= explicit
  676             &= help "Line width for pretty printing.\nDefault: 120"
  677         }   &= name "validate-solution"
  678             &= explicit
  679             &= help "Validating a solution."
  680     , Solve
  681         { essence
  682             = def
  683             &= typ "ESSENCE_FILE"
  684             &= argPos 0
  685         , essenceParams
  686             = []
  687             &= typ "PARAMETER_FILE(s)"
  688             &= args
  689         , validateSolutionsOpt
  690             = False
  691             &= name "validate-solutions"
  692             &= groupname "General"
  693             &= explicit
  694             &= help "Enable solution validation."
  695         , outputDirectory
  696             = "conjure-output"
  697             &= typDir
  698             &= name "output-directory"
  699             &= name "o"
  700             &= groupname "Logging & Output"
  701             &= explicit
  702             &= help "Where to save generated models.\n\
  703                     \Default value: 'conjure-output'"
  704         , numberingStart
  705             = 1
  706             &= name "numbering-start"
  707             &= groupname "Logging & Output"
  708             &= explicit
  709             &= help "Starting value for output files.\n\
  710                     \Default value: 1"
  711         , smartFilenames
  712             = False
  713             &= name "smart-filenames"
  714             &= groupname "Logging & Output"
  715             &= explicit
  716             &= help "Use \"smart names\" for models.\n\
  717                     \Directs Conjure to use the answers when producing \
  718                     \a filename and to ignore the order of questions. \
  719                     \Only useful if 'f' is used for questions."
  720         , responses
  721             = ""
  722             &= name "responses"
  723             &= groupname "Model generation"
  724             &= explicit
  725             &= help "A comma separated list of integers.\n\
  726                     \If provided, these will be used as the answers during \
  727                     \interactive model generation instead of prompting the user."
  728         , responsesRepresentation
  729             = ""
  730             &= name "responses-representation"
  731             &= groupname "Model generation"
  732             &= explicit
  733             &= help "A comma separated list of variable name : integer pairs.\n\
  734                     \If provided, these will be used as the answers during \
  735                     \interactive model generation instead of prompting the user \
  736                     \for the variable representation questions.\n\
  737                     \See --dump-representations for a list of available representation options."
  738         , solutionsInOneFile
  739             = False
  740             &= name "solutions-in-one-file"
  741             &= groupname "Logging & Output"
  742             &= explicit
  743             &= help "Place all solutions in a single file instead of generating a separate file per solution.\n\
  744                     \Off by default."
  745         , runsolverCPUTimeLimit
  746             = def
  747             &= name "runsolver-cpu-time-limit"
  748             &= groupname "runsolver"
  749             &= explicit
  750             &= help "Use runsolver to limit total CPU time (in seconds)"
  751         , runsolverWallTimeLimit
  752             = def
  753             &= name "runsolver-wall-time-limit"
  754             &= groupname "runsolver"
  755             &= explicit
  756             &= help "Use runsolver to limit total elapsed time (in seconds)"
  757         , runsolverMemoryLimit
  758             = def
  759             &= name "runsolver-memory-limit"
  760             &= groupname "runsolver"
  761             &= explicit
  762             &= help "Use runsolver to limit total memory usage (Maximum RSS - in megabytes)."
  763         , logLevel
  764             = def
  765             &= name "log-level"
  766             &= groupname "Logging & Output"
  767             &= explicit
  768             &= help "Log level."
  769         , verboseTrail
  770             = False
  771             &= name "verbose-trail"
  772             &= groupname "Logging & Output"
  773             &= explicit
  774             &= help "Generate verbose trails."
  775         , rewritesTrail
  776             = False
  777             &= name "rewrites-trail"
  778             &= groupname "Logging & Output"
  779             &= explicit
  780             &= help "Generate trails about the applied rewritings."
  781         , logRuleFails
  782             = False
  783             &= name "log-rule-fails"
  784             &= groupname "Logging & Output"
  785             &= explicit
  786             &= help "Generate logs for rule failures. (Caution: can be a lot!)"
  787         , logRuleSuccesses
  788             = False
  789             &= name "log-rule-successes"
  790             &= groupname "Logging & Output"
  791             &= explicit
  792             &= help "Generate logs for rule applications."
  793         , logRuleAttempts
  794             = False
  795             &= name "log-rule-attempts"
  796             &= groupname "Logging & Output"
  797             &= explicit
  798             &= help "Generate logs for rule attempts. (Caution: can be a lot!)"
  799         , logChoices
  800             = False
  801             &= name "log-choices"
  802             &= groupname "Logging & Output"
  803             &= explicit
  804             &= help "Store the choices in a way that can be reused by -al"
  805         , portfolio
  806             = Nothing
  807             &= typ "PORTFOLIO"
  808             &= name "portfolio"
  809             &= groupname "Model generation"
  810             &= explicit
  811             &= help "Portfolio size. When it is set to N, Conjure will try to generate up to N models."
  812         , strategyQ
  813             = "f"
  814             &= typ "STRATEGY"
  815             &= name "strategy-q"
  816             &= name "q"
  817             &= groupname "Model generation"
  818             &= explicit
  819             &= help "Strategy for selecting the next question to answer. \
  820                     \Options: f (for first), i (for interactive), r (for random), x (for all). \
  821                     \Prepend a (for auto) to automatically skip \
  822                     \when there is only one option at any point.\n\
  823                     \Default value: f"
  824         , strategyA
  825             = "c"
  826             &= typ "STRATEGY"
  827             &= name "strategy-a"
  828             &= name "a"
  829             &= groupname "Model generation"
  830             &= explicit
  831             &= help "Strategy for selecting an answer. Same options as strategy-q.\n\
  832                     \ c picks the most 'compact' option \
  833                     \at every decision point.\n\
  834                     \ s picks the 'sparsest' option \
  835                     \at every decision point: \
  836                     \useful for --representations-givens\n\
  837                     \Default value: c"
  838         , representations
  839             = Nothing
  840             &= typ "STRATEGY"
  841             &= name "representations"
  842             &= groupname "Model generation"
  843             &= explicit
  844             &= help "Strategy for choosing a representation.\n\
  845                     \Default value: same as --strategy-a"
  846         , representationsFinds
  847             = Nothing
  848             &= typ "STRATEGY"
  849             &= name "representations-finds"
  850             &= groupname "Model generation"
  851             &= explicit
  852             &= help "Strategy for choosing a representation for a decision variable.\n\
  853                     \Default value: same as --representations"
  854         , representationsGivens
  855             = Nothing
  856             &= typ "STRATEGY"
  857             &= name "representations-givens"
  858             &= groupname "Model generation"
  859             &= explicit
  860             &= help "Strategy for choosing a representation for a parameter.\n\
  861                     \Default value: s (for sparse)"
  862         , representationsAuxiliaries
  863             = Nothing
  864             &= typ "STRATEGY"
  865             &= name "representations-auxiliaries"
  866             &= groupname "Model generation"
  867             &= explicit
  868             &= help "Strategy for choosing a representation for an auxiliary variable.\n\
  869                     \Default value: same as --representations"
  870         , representationsQuantifieds
  871             = Nothing
  872             &= typ "STRATEGY"
  873             &= name "representations-quantifieds"
  874             &= groupname "Model generation"
  875             &= explicit
  876             &= help "Strategy for choosing a representation for a quantified variable.\n\
  877                     \Default value: same as --representations"
  878         , representationsCuts
  879             = Nothing
  880             &= typ "STRATEGY"
  881             &= name "representations-cuts"
  882             &= groupname "Model generation"
  883             &= explicit
  884             &= help "Strategy for choosing a representation for cuts in 'branching on'.\n\
  885                     \Default value: same as --representations"
  886         , channelling
  887             = True
  888             &= name "channelling"
  889             &= groupname "Model generation"
  890             &= explicit
  891             &= help "Whether to produce channelled models \
  892                     \(true by default).\n"
  893         , representationLevels
  894             = True
  895             &= name "representation-levels"
  896             &= groupname "Model generation"
  897             &= explicit
  898             &= help "Whether to use built-in precedence levels when choosing representations. \
  899                     \Used to cut down the number of generated models.\n\
  900                     \Default: true"
  901         , followModel
  902             = ""
  903             &= name "follow-model"
  904             &= groupname "Model generation"
  905             &= explicit
  906             &= help "Provide a Conjure-generated Essence Prime model to be used as a guide during model generation. \
  907                     \Conjure will try to imitate the modelling decisions from this file."
  908         , seed
  909             = Nothing
  910             &= name "seed"
  911             &= groupname "Model generation"
  912             &= explicit
  913             &= help "Random number generator seed."
  914         , limitModels
  915             = Nothing
  916             &= name "limit-models"
  917             &= groupname "Model generation"
  918             &= explicit
  919             &= help "Maximum number of models to generate."
  920         , limitTime
  921             = Nothing
  922             &= name "limit-time"
  923             &= groupname "General"
  924             &= explicit
  925             &= help "Limit in seconds of real time."
  926         , useExistingModels
  927             = []
  928             &= name "use-existing-models"
  929             &= groupname "Model generation"
  930             &= explicit
  931             &= typFile
  932             &= help "File names of Essence' models generated beforehand.\n\
  933                     \If given, Conjure skips the modelling phase and uses the existing models for solving.\n\
  934                     \The models should be inside the output directory (See -o)."
  935         , savilerowOptions
  936             = def
  937             &= name "savilerow-options"
  938             &= groupname "Options for other tools"
  939             &= explicit
  940             &= help "Options passed to Savile Row."
  941         , solverOptions
  942             = def
  943             &= name "solver-options"
  944             &= groupname "Options for other tools"
  945             &= explicit
  946             &= help "Options passed to the backend solver."
  947         , solver
  948             = "minion"
  949             &= name "solver"
  950             &= groupname "Options for other tools"
  951             &= explicit
  952             &= help "Backend solver. \
  953                     \Possible values:\n\
  954                     \ - minion (CP solver)\n\
  955                     \ - gecode (CP solver)\n\
  956                     \ - chuffed (CP solver)\n\
  957                     \ - or-tools (CP solver)\n\
  958                     \ - glucose (SAT solver)\n\
  959                     \ - glucose-syrup (SAT solver)\n\
  960                     \ - lingeling/plingeling/treengeling (SAT solver)\n\
  961                     \ - cadical (SAT solver)\n\
  962                     \ - kissat (SAT solver)\n\
  963                     \ - minisat (SAT solver)\n\
  964                     \ - bc_minisat_all (AllSAT solver, only works with --number-of-solutions=all)\n\
  965                     \ - nbc_minisat_all (AllSAT solver, only works with --number-of-solutions=all)\n\
  966                     \ - open-wbo (MaxSAT solver, only works with optimisation problems)\n\
  967                     \ - coin-or (MIP solver, implemented via MiniZinc)\n\
  968                     \ - cplex (MIP solver, implemented via MiniZinc)\n\
  969                     \ - boolector (SMT solver, supported logics: bv)\n\
  970                     \ - yices (SMT solver, supported logics: bv, lia, idl)\n\
  971                     \ - z3 (SMT solver, supported logics: bv, lia, nia, idl)\n\
  972                     \Default: minion\n\n\
  973                     \Default logic for SMT solvers is bitvector (bv).\n\
  974                     \Append a dash and the name of a logic to the solver name to choose a different logic. For example yices-idl."
  975         , graphSolver
  976             = False
  977             &= name "graph-solver"
  978             &= groupname "General"
  979             &= explicit
  980             &= help "Create input files for the Glasgow graph solver."
  981         , cgroups
  982             = False
  983             &= name "cgroups"
  984             &= groupname "General"
  985             &= explicit
  986             &= help "Setup and use cgroups when solving with Savile Row."
  987         , nbSolutions
  988             = "1"
  989             &= name "number-of-solutions"
  990             &= groupname "General"
  991             &= explicit
  992             &= help "Number of solutions to find; \
  993                     \\"all\" enumerates all solutions.\n\
  994                     \Default: 1"
  995         , copySolutions
  996             = True
  997             &= name "copy-solutions"
  998             &= groupname "General"
  999             &= explicit
 1000             &= help "Whether to place a copy of solution(s) next to the Essence file or not.\n\
 1001                     \Default: on"
 1002         , outputFormat
 1003             = def
 1004             &= name "output-format"
 1005             &= groupname "Logging & Output"
 1006             &= explicit
 1007             &= typ "FORMAT"
 1008             &= help "Format to use for output. All output formats can also be used for input.\n\
 1009                     \    plain: default\n\
 1010                     \    binary: a binary encoding\n\
 1011                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1012                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1013                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1014                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1015         , lineWidth
 1016             = 120
 1017             &= name "line-width"
 1018             &= groupname "Logging & Output"
 1019             &= explicit
 1020             &= help "Line width for pretty printing.\nDefault: 120"
 1021         , generateStreamliners
 1022             = ""
 1023             &= name "generate-streamliners"
 1024             &= groupname "Streamlining"
 1025             &= explicit
 1026             &= help "A comma separated list of integers.\n\
 1027                     \If provided, the streamlining constraints that correspond to the given integers will be generated.\n\
 1028                     \Run \"conjure streamlining ESSENCE_FILE\" to generate a list of all applicable streamliners."
 1029         }   &= name "solve"
 1030             &= explicit
 1031             &= help "A combined mode for convenience.\n\
 1032                     \Runs Conjure in modelling mode followed by \
 1033                     \parameter translation if required, \
 1034                     \then Savile Row + Minion to solve, and \
 1035                     \then solution translation."
 1036     , IDE
 1037         { essence
 1038             = def
 1039             &= typ "ESSENCE_FILE"
 1040             &= argPos 0
 1041         , dumpDeclarations
 1042             = False
 1043             &= name "dump-declarations"
 1044             &= groupname "IDE Features"
 1045             &= explicit
 1046             &= help "Print information about top level declarations."
 1047         , dumpRepresentations
 1048             = False
 1049             &= name "dump-representations"
 1050             &= groupname "IDE Features"
 1051             &= explicit
 1052             &= help "List the available representations for decision variables and parameters."
 1053         , logLevel
 1054             = def
 1055             &= name "log-level"
 1056             &= groupname "Logging & Output"
 1057             &= explicit
 1058             &= help "Log level."
 1059         , limitTime
 1060             = Nothing
 1061             &= name "limit-time"
 1062             &= groupname "General"
 1063             &= explicit
 1064             &= help "Limit in seconds of real time."
 1065         , lineWidth
 1066             = 120
 1067             &= name "line-width"
 1068             &= groupname "Logging & Output"
 1069             &= explicit
 1070             &= help "Line width for pretty printing.\nDefault: 120"
 1071         }   &= name "ide"
 1072             &= explicit
 1073             &= help "IDE support features for Conjure.\n\
 1074                     \Not intended for direct use."
 1075     , Pretty
 1076         { essence
 1077             = def
 1078             &= typ "ESSENCE_FILE"
 1079             &= argPos 0
 1080         , logLevel
 1081             = def
 1082             &= name "log-level"
 1083             &= groupname "Logging & Output"
 1084             &= explicit
 1085             &= help "Log level."
 1086         , normaliseQuantified
 1087             = False
 1088             &= name "normalise-quantified"
 1089             &= explicit
 1090             &= help "Normalise the names of quantified variables."
 1091         , removeUnused
 1092             = False
 1093             &= name "remove-unused"
 1094             &= explicit
 1095             &= help "Remove unused declarations."
 1096         , limitTime
 1097             = Nothing
 1098             &= name "limit-time"
 1099             &= groupname "General"
 1100             &= explicit
 1101             &= help "Limit in seconds of real time."
 1102         , outputFormat
 1103             = def
 1104             &= name "output-format"
 1105             &= groupname "Logging & Output"
 1106             &= explicit
 1107             &= typ "FORMAT"
 1108             &= help "Format to use for output. All output formats can also be used for input.\n\
 1109                     \    plain: default\n\
 1110                     \    binary: a binary encoding\n\
 1111                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1112                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1113                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1114                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1115         , lineWidth
 1116             = 120
 1117             &= name "line-width"
 1118             &= groupname "Logging & Output"
 1119             &= explicit
 1120             &= help "Line width for pretty printing.\nDefault: 120"
 1121         }   &= name "pretty"
 1122             &= explicit
 1123             &= help "Pretty print as Essence file to stdout.\n\
 1124                     \This mode can be used to view a binary Essence file in textual form."
 1125     , Diff
 1126         { file1
 1127             = def
 1128             &= typFile
 1129             &= argPos 0
 1130         , file2
 1131             = def
 1132             &= typFile
 1133             &= argPos 1
 1134         , logLevel
 1135             = def
 1136             &= name "log-level"
 1137             &= groupname "Logging & Output"
 1138             &= explicit
 1139             &= help "Log level."
 1140         , limitTime
 1141             = Nothing
 1142             &= name "limit-time"
 1143             &= groupname "General"
 1144             &= explicit
 1145             &= help "Limit in seconds of real time."
 1146         , outputFormat
 1147             = def
 1148             &= name "output-format"
 1149             &= groupname "Logging & Output"
 1150             &= explicit
 1151             &= typ "FORMAT"
 1152             &= help "Format to use for output. All output formats can also be used for input.\n\
 1153                     \    plain: default\n\
 1154                     \    binary: a binary encoding\n\
 1155                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1156                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1157                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1158                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1159         , lineWidth
 1160             = 120
 1161             &= name "line-width"
 1162             &= groupname "Logging & Output"
 1163             &= explicit
 1164             &= help "Line width for pretty printing.\nDefault: 120"
 1165         }   &= name "diff"
 1166             &= explicit
 1167             &= help "Diff on two Essence files. Works on models, parameters, and solutions."
 1168     , TypeCheck
 1169         { essence
 1170             = def
 1171             &= typ "ESSENCE_FILE"
 1172             &= argPos 0
 1173         , logLevel
 1174             = def
 1175             &= name "log-level"
 1176             &= groupname "Logging & Output"
 1177             &= explicit
 1178             &= help "Log level."
 1179         , limitTime
 1180             = Nothing
 1181             &= name "limit-time"
 1182             &= groupname "General"
 1183             &= explicit
 1184             &= help "Limit in seconds of real time."
 1185         }   &= name "type-check"
 1186             &= explicit
 1187             &= help "Type-checking a single Essence file."
 1188     , Split
 1189         { essence
 1190             = def
 1191             &= typ "ESSENCE_FILE"
 1192             &= argPos 0
 1193         , outputDirectory
 1194             = "conjure-output"
 1195             &= typDir
 1196             &= name "output-directory"
 1197             &= name "o"
 1198             &= groupname "Logging & Output"
 1199             &= explicit
 1200             &= help "Where to save generated models.\n\
 1201                     \Default value: 'conjure-output'"
 1202         , logLevel
 1203             = def
 1204             &= name "log-level"
 1205             &= groupname "Logging & Output"
 1206             &= explicit
 1207             &= help "Log level."
 1208         , limitTime
 1209             = Nothing
 1210             &= name "limit-time"
 1211             &= groupname "General"
 1212             &= explicit
 1213             &= help "Limit in seconds of real time."
 1214         , outputFormat
 1215             = def
 1216             &= name "output-format"
 1217             &= groupname "Logging & Output"
 1218             &= explicit
 1219             &= typ "FORMAT"
 1220             &= help "Format to use for output. All output formats can also be used for input.\n\
 1221                     \    plain: default\n\
 1222                     \    binary: a binary encoding\n\
 1223                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1224                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1225                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1226                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1227         , lineWidth
 1228             = 120
 1229             &= name "line-width"
 1230             &= groupname "Logging & Output"
 1231             &= explicit
 1232             &= help "Line width for pretty printing.\nDefault: 120"
 1233         }   &= name "split"
 1234             &= explicit
 1235             &= help "Split an Essence file to various smaller files. Useful for testing."
 1236     , SymmetryDetection
 1237         { essence
 1238             = def
 1239             &= typ "ESSENCE_FILE"
 1240             &= argPos 0
 1241         , json
 1242             = def
 1243             &= typ "JSON_FILE"
 1244             &= name "json"
 1245             &= groupname "Logging & Output"
 1246             &= explicit
 1247             &= help "Output JSON file.\n\
 1248                     \Default is 'foo.essence-json'\n\
 1249                     \if the Essence file is named 'foo.essence'"
 1250         , logLevel
 1251             = def
 1252             &= name "log-level"
 1253             &= groupname "Logging & Output"
 1254             &= explicit
 1255             &= help "Log level."
 1256         , limitTime
 1257             = Nothing
 1258             &= name "limit-time"
 1259             &= groupname "General"
 1260             &= explicit
 1261             &= help "Limit in seconds of real time."
 1262         , outputFormat
 1263             = def
 1264             &= name "output-format"
 1265             &= groupname "Logging & Output"
 1266             &= explicit
 1267             &= typ "FORMAT"
 1268             &= help "Format to use for output. All output formats can also be used for input.\n\
 1269                     \    plain: default\n\
 1270                     \    binary: a binary encoding\n\
 1271                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1272                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1273                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1274                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1275         , lineWidth
 1276             = 120
 1277             &= name "line-width"
 1278             &= groupname "Logging & Output"
 1279             &= explicit
 1280             &= help "Line width for pretty printing.\nDefault: 120"
 1281         }   &= name "symmetry-detection"
 1282             &= explicit
 1283             &= help "Dump some JSON to be used as input to ferret for symmetry detection."
 1284     , ParameterGenerator
 1285         { essence
 1286             = def
 1287             &= typ "ESSENCE_FILE"
 1288             &= argPos 0
 1289         , minInt
 1290             = 0
 1291             &= typ "INT"
 1292             &= name "MININT"
 1293             &= groupname "Integer bounds"
 1294             &= explicit
 1295             &= help "The minimum integer value for the parameter values.\nDefault: 0"
 1296         , maxInt
 1297             = 100
 1298             &= typ "INT"
 1299             &= name "MAXINT"
 1300             &= groupname "Integer bounds"
 1301             &= explicit
 1302             &= help "The maximum integer value for the parameter values.\nDefault: 100"
 1303         , logLevel
 1304             = def
 1305             &= name "log-level"
 1306             &= groupname "Logging & Output"
 1307             &= explicit
 1308             &= help "Log level."
 1309         , limitTime
 1310             = Nothing
 1311             &= name "limit-time"
 1312             &= groupname "General"
 1313             &= explicit
 1314             &= help "Limit in seconds of real time."
 1315         , outputFormat
 1316             = def
 1317             &= name "output-format"
 1318             &= groupname "Logging & Output"
 1319             &= explicit
 1320             &= typ "FORMAT"
 1321             &= help "Format to use for output. All output formats can also be used for input.\n\
 1322                     \    plain: default\n\
 1323                     \    binary: a binary encoding\n\
 1324                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1325                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1326                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1327                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1328         , lineWidth
 1329             = 120
 1330             &= name "line-width"
 1331             &= groupname "Logging & Output"
 1332             &= explicit
 1333             &= help "Line width for pretty printing.\nDefault: 120"
 1334         }   &= name "parameter-generator"
 1335             &= explicit
 1336             &= help "Generate an Essence model describing the instances of the problem class \
 1337                     \defined in the input Essence model.\n\
 1338                     \An error will be printed if the model has infinitely many instances."
 1339     , AutoIG
 1340         { essence
 1341             = def
 1342             &= typ "ESSENCE_FILE"
 1343             &= argPos 0
 1344         , outputFilepath
 1345             = def
 1346             &= typ "OUTPUT_FILE"
 1347             &= argPos 1
 1348         , generatorToIrace
 1349             = False
 1350             &= name "generator-to-irace"
 1351             &= explicit
 1352             &= help "Convert the givens in a hand written generator model to irace syntax."
 1353         , removeAux
 1354             = False
 1355             &= name "remove-aux"
 1356             &= explicit
 1357             &= help "Remove lettings whose name start with Aux"
 1358         , logLevel
 1359             = def
 1360             &= name "log-level"
 1361             &= groupname "Logging & Output"
 1362             &= explicit
 1363             &= help "Log level."
 1364         , limitTime
 1365             = Nothing
 1366             &= name "limit-time"
 1367             &= groupname "General"
 1368             &= explicit
 1369             &= help "Limit in seconds of real time."
 1370         , outputFormat
 1371             = def
 1372             &= name "output-format"
 1373             &= groupname "Logging & Output"
 1374             &= explicit
 1375             &= typ "FORMAT"
 1376             &= help "Format to use for output. All output formats can also be used for input.\n\
 1377                     \    plain: default\n\
 1378                     \    binary: a binary encoding\n\
 1379                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1380                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1381                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1382                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1383         , lineWidth
 1384             = 120
 1385             &= name "line-width"
 1386             &= groupname "Logging & Output"
 1387             &= explicit
 1388             &= help "Line width for pretty printing.\nDefault: 120"
 1389         }   &= name "autoig"
 1390             &= explicit
 1391             &= help "Functionality to support the AutoIG workflow."
 1392     , Boost
 1393         { essence
 1394             = def
 1395             &= typ "ESSENCE_FILE"
 1396             &= argPos 0
 1397         , logLevel
 1398             = def
 1399             &= name "log-level"
 1400             &= groupname "Logging & Output"
 1401             &= explicit
 1402             &= help "Log level."
 1403         , logRuleSuccesses
 1404             = False
 1405             &= name "log-rule-successes"
 1406             &= groupname "Logging & Output"
 1407             &= explicit
 1408             &= help "Generate logs for rule applications."
 1409         , limitTime
 1410             = Nothing
 1411             &= name "limit-time"
 1412             &= groupname "General"
 1413             &= explicit
 1414             &= help "Time limit in seconds (real time)."
 1415         , outputFormat
 1416             = def
 1417             &= name "output-format"
 1418             &= groupname "Logging & Output"
 1419             &= explicit
 1420             &= typ "FORMAT"
 1421             &= help "Format to use for output. All output formats can also be used for input.\n\
 1422                     \    plain: default\n\
 1423                     \    binary: a binary encoding\n\
 1424                     \    astjson: a JSON dump of the internal data structures, quite verbose\n\
 1425                     \    json: a simplified JSON format, only used for parameters and solutions\n\
 1426                     \    jsonstream: same as JSON, except in one special case. when multiple solutions are saved in a single file as json, this mode prints one solution per line\n\
 1427                     \    minizinc: minizinc format for data files, only used for solutions\n"
 1428         , lineWidth
 1429             = 120
 1430             &= name "line-width"
 1431             &= groupname "Logging & Output"
 1432             &= explicit
 1433             &= help "Line width to use during pretty printing.\nDefault: 120"
 1434         }   &= name "boost"
 1435             &= explicit
 1436             &= help "Strengthen an Essence model as described in \"Reformulating \
 1437                     \Essence Specifications for Robustness\",\n\
 1438                     \which aims to make search faster."
 1439     , Streamlining
 1440         { essence
 1441             = def
 1442             &= typ "ESSENCE_FILE"
 1443             &= argPos 0
 1444         , logLevel
 1445             = def
 1446             &= name "log-level"
 1447             &= groupname "Logging & Output"
 1448             &= explicit
 1449             &= help "Log level."
 1450         , limitTime
 1451             = Nothing
 1452             &= name "limit-time"
 1453             &= groupname "General"
 1454             &= explicit
 1455             &= help "Time limit in seconds (real time)."
 1456         , outputFormat
 1457             = def
 1458             &= name "output-format"
 1459             &= groupname "Logging & Output"
 1460             &= explicit
 1461             &= typ "FORMAT"
 1462             &= help "Conjure's output can be in multiple formats.\n\
 1463                     \    plain : The default\n\
 1464                     \    binary: A binary encoding of the Essence output.\n\
 1465                     \            It can be read back in by Conjure.\n\
 1466                     \    json  : A json encoding of the Essence output.\n\
 1467                     \            It can be used by other tools integrating with Conjure\n\
 1468                     \            in order to avoid having to parse textual Essence."
 1469         , lineWidth
 1470             = 120
 1471             &= name "line-width"
 1472             &= groupname "Logging & Output"
 1473             &= explicit
 1474             &= help "Line width to use during pretty printing.\nDefault: 120"
 1475         }   &= name "streamlining"
 1476             &= explicit
 1477             &= help "Generate streamlined Essence models."
 1478     , LSP {
 1479         logLevel = def,
 1480         limitTime = Nothing
 1481     } &= name "lsp"
 1482     ]      &= program "conjure"
 1483            &= helpArg [explicit, name "help"]
 1484            &= versionArg [explicit, name "version"]
 1485            &= summary (unlines [ "Conjure: The Automated Constraint Modelling Tool"
 1486                                , versionLine
 1487                                ])
 1488            &= help "The command line interface of Conjure takes a command name as the first argument \
 1489                    \followed by more arguments depending on the command.\n\
 1490                    \This help text gives a list of the available commands.\n\
 1491                    \For details of a command, pass the --help flag after the command name.\n\
 1492                    \For example: 'conjure translate-solution --help'"
 1493 
 1494 versionLine :: String
 1495 versionLine = "Conjure v" ++ showVersion version ++ " (Repository version " ++ repositoryVersion ++ ")"