{- CAO Compiler Copyright (C) 2014 Cryptography and Information Security Group, HASLab - INESC TEC and Universidade do Minho This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {-# LANGUAGE DeriveDataTypeable #-} {-# OPTIONS_GHC -fno-cse #-} {- Module : $Header$ Description : Compilation flags Copyright : (C) 2014 Cryptography and Information Security Group, HASLab - INESC TEC and Universidade do Minho License : GPL Maintainer : Paulo Silva Stability : experimental Portability : non-portable -} module Main.Flags ( Options(..) , RunMode(..) , getOpts , printHelp ) where import System.Console.CmdArgs import System.Environment data RunMode = CAO | CAO_Strict | CALF | CALF_Strict deriving (Show, Data, Typeable) data Options = Comp { input :: FilePath , dependent :: Bool , verbose :: Bool , output :: Maybe FilePath , config :: FilePath , runmode :: RunMode , ddump_tc :: Bool , ddump_simpl :: Bool , ddump_eval :: Bool , ddump_expand :: Bool , ddump_opt :: Bool , ddump_target :: Bool , ddump_prec :: Bool , dgen_cfg :: Maybe String , dgen_ssa :: Maybe String , dcheck :: Bool , fexpand :: Bool , optimize :: Bool , findist_fun :: Maybe (String, String) } | Help deriving (Show, Data, Typeable) comp :: Options comp = Comp { input = def &= args &= typ "FILE" , dependent = def &= help "Turns on the dependent type checking" , runmode = enum [ CALF &= help "Normal mode" , CALF_Strict &= help "Access checking" , CAO &= help "Type checking without symbolic constants" , CAO_Strict &= help "Type checking without symbolic constants (with access checking)"] &= help "Running mode" , verbose = def &= help "Give verbose output" , output = def &= typ "FILE" &= help "Output file" , config = "default.plat" &= typ "FILE" &= help "Config file" , ddump_tc = def &= help "Dump type-checked code" &= groupname "Debugging" , ddump_simpl = def &= help "Dump simplified code" &= groupname "Debugging" , ddump_eval = def &= help "Dump code with evaluated expressions" &= groupname "Debugging" , ddump_expand = def &= help "Dump code after seq expansion" &= groupname "Debugging" , ddump_opt = def &= help "Dump code after optimization passes" &= groupname "Debugging" , ddump_target = def &= help "Dump code after targeting it to a given platform" &= groupname "Debugging" , ddump_prec = def &= help "Dump code after preprocessing to a C translation" &= groupname "Debugging" , dgen_cfg = def &= opt "pdf" &= typ "FORMAT" &= help "Generate Cao CFG in the specified\ \ output format (Must be supported\ \ by graphviz 'dot'!. Default = pdf)" &= groupname "Debugging" , dgen_ssa = def &= opt "pdf" &= typ "FORMAT" &= help "Generate Cao CFG in SSA in the\ \ output format (Must be supported\ \ by graphviz 'dot'!. Default = pdf)" &= groupname "Debugging" , dcheck = def &= help "Type check dumped code" &= groupname "Debugging" , fexpand = def &= explicit &= name "fexpand" &= help "Expand seqs" &= groupname "Optimization options" , optimize = def &= explicit &= name "O" &= help "Run optimization passes" &= groupname "Optimization options" , findist_fun = def &= explicit &= name "findist-fun" &= typ "FUN,FUN" &= help "Apply side channel countermeasures\ \ to two function definitions." &= groupname "Optimization options" } &= help "CAO to C compiler" chelp :: Options chelp = Help &= help "Display help about CAO modes" mode :: Mode (CmdArgs Options) mode = cmdArgsMode $ modes [comp, chelp] &= help "CAO compiler infraestructure" &= summary "cao v0.1 \n\ \(C) SMART Team 2011 - DI/HasLab - Univ. Minho,\ \ Braga, Portugal" printHelp :: IO () printHelp = withArgs ["--help"] $ cmdArgsRun mode >> return () getOpts :: IO Options getOpts = getArgs >>= doGetOpts where doGetOpts as | null as = withArgs ["help"] $ cmdArgsRun mode | otherwise = cmdArgsRun mode