--  C -> Haskell Compiler: management of switches
--
--  Author : Manuel M T Chakravarty
--  Created: 6 March 99
--
--  Version $Revision: 1.3 $ from $Date: 2005/06/22 16:01:21 $
--
--  Copyright (c) [1999..2004] Manuel M T Chakravarty
--
--  This file 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 2 of the License, or
--  (at your option) any later version.
--
--  This file 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.
--
--- DESCRIPTION ---------------------------------------------------------------
--
--  This module manages C2HS's compiler switches. It exports the data types
--  used to store the switches and operations on them.
--
--- DOCU ----------------------------------------------------------------------
--
--  language: Haskell 98
--
--  Overview over the switches:
--
--  * The cpp options specify the options passed to the C preprocessor.
--
--  * The cpp filename gives the name of the executable of the C preprocessor.
--
--  * The `hpaths' switch lists all directories that should be considered when
--    searching for a header file.
--
--  * The `keep' flag says whether the intermediate file produced by the C
--    pre-processor should be retained or not.
--
--  * Traces specify which trace information should be output by the compiler.
--    Currently the following trace information is supported:
--
--    - information about phase activation and phase completion
--
--  * After processing the compiler options, `outputSB' contains the base name
--    for the generated Haskell, C header, and .chi files.  However, during
--    processing compiler options, `outputSB' contains arguments to the
--    `--output' option and `outDirSB' contains arguments to the
--    `--output-dir' option.
--
--  * The pre-compiled header switch is unset if no pre-compiled header should
--    be read or generated. If the option is set and a header file is given
--    a concise version of the header will be written to the FilePath. If
--    a binding file is given, the pre-compiled header is used to expand the
--    module unless the binding file contains itself C declarations.
--
--- TODO ----------------------------------------------------------------------
--

module Switches (
  SwitchBoard(..), Traces(..), initialSwitchBoard
) where


-- the switch board contains all toolkit switches
-- ----------------------------------------------

-- all switches of the toolkit (EXPORTED)
--
data SwitchBoard = SwitchBoard {
                     SwitchBoard -> [String]
cppOptsSB :: [String],     -- cpp options
                     SwitchBoard -> String
cppSB     :: FilePath,     -- cpp executable
                     SwitchBoard -> [String]
hpathsSB  :: [FilePath],   -- header file directories
                       -- since 0.11.1 `hpathsSB' isn't really needed anymore..
                       -- ..remove from 0.12 series
                     SwitchBoard -> Bool
keepSB    :: Bool,         -- keep intermediate file
                     SwitchBoard -> Traces
tracesSB  :: Traces,       -- trace flags
                     SwitchBoard -> String
outputSB  :: FilePath,     -- basename of generated files
                     SwitchBoard -> String
outDirSB  :: FilePath,     -- dir where generated files go
                     SwitchBoard -> String
headerSB  :: FilePath,     -- generated header file
                     SwitchBoard -> Maybe String
preCompSB :: Maybe FilePath,-- optional binary header r/w
                     SwitchBoard -> Bool
oldFFI    :: Bool,         -- GHC 4.XX compatible code
                     SwitchBoard -> [String]
chiPathSB :: [FilePath],   -- .chi file directories
                     SwitchBoard -> Maybe String
lockFunSB :: Maybe String  -- a function to wrap each call
                   }

-- switch states on startup (EXPORTED)
--
initialSwitchBoard :: SwitchBoard
initialSwitchBoard :: SwitchBoard
initialSwitchBoard  = SwitchBoard :: [String]
-> String
-> [String]
-> Bool
-> Traces
-> String
-> String
-> String
-> Maybe String
-> Bool
-> [String]
-> Maybe String
-> SwitchBoard
SwitchBoard {
                        cppOptsSB :: [String]
cppOptsSB = [],
                        cppSB :: String
cppSB     = String
"cpp",
                        hpathsSB :: [String]
hpathsSB  = [],
                        keepSB :: Bool
keepSB    = Bool
False,
                        tracesSB :: Traces
tracesSB  = Traces
initialTraces,
                        outputSB :: String
outputSB  = String
"",
                        outDirSB :: String
outDirSB  = String
"",
                        headerSB :: String
headerSB  = String
"",
                        preCompSB :: Maybe String
preCompSB = Maybe String
forall a. Maybe a
Nothing,
                        oldFFI :: Bool
oldFFI    = Bool
False,
                        chiPathSB :: [String]
chiPathSB = [String
"."],
                        lockFunSB :: Maybe String
lockFunSB = Maybe String
forall a. Maybe a
Nothing
                      }


-- traces
-- ------

-- different kinds of traces possible (EXPORTED)
--
data Traces = Traces {
                Traces -> Bool
tracePhasesSW  :: Bool,
                Traces -> Bool
traceGenBindSW :: Bool,
                Traces -> Bool
traceCTravSW   :: Bool,
                Traces -> Bool
dumpCHSSW      :: Bool
              }

-- trace setting on startup
--
--  * all traces are initially off
--
initialTraces :: Traces
initialTraces :: Traces
initialTraces  = Traces :: Bool -> Bool -> Bool -> Bool -> Traces
Traces {
                   tracePhasesSW :: Bool
tracePhasesSW  = Bool
False,
                   traceGenBindSW :: Bool
traceGenBindSW = Bool
False,
                   traceCTravSW :: Bool
traceCTravSW   = Bool
False,
                   dumpCHSSW :: Bool
dumpCHSSW      = Bool
False
                 }