ghc-mod/Language/Haskell/GhcMod/Types.hs

133 lines
3.7 KiB
Haskell

module Language.Haskell.GhcMod.Types where
import Control.Monad.Trans.Control (MonadBaseControl)
import Data.List (intercalate)
import qualified Data.Map as M
import Exception (ExceptionMonad)
import MonadUtils (MonadIO)
import PackageConfig (PackageConfig)
-- | A constraint alias (-XConstraintKinds) to make functions dealing with
-- 'GhcModT' somewhat cleaner.
--
-- Basicially an @IOish m => m@ is a 'Monad' supporting arbitrary 'IO' and
-- exception handling. Usually this will simply be 'IO' but we parametrise it in
-- the exported API so users have the option to use a custom inner monad.
type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m)
-- | Output style.
data OutputStyle = LispStyle -- ^ S expression style.
| PlainStyle -- ^ Plain textstyle.
deriving (Show)
-- | The type for line separator. Historically, a Null string is used.
newtype LineSeparator = LineSeparator String deriving (Show)
data Options = Options {
outputStyle :: OutputStyle
-- | Line separator string.
, lineSeparator :: LineSeparator
-- | @ghc@ program name.
, ghcProgram :: FilePath
-- | @cabal@ program name.
, cabalProgram :: FilePath
-- | GHC command line options set on the @ghc-mod@ command line
, ghcUserOptions:: [GHCOption]
-- | If 'True', 'browse' also returns operators.
, operators :: Bool
-- | If 'True', 'browse' also returns types.
, detailed :: Bool
-- | If 'True', 'browse' will return fully qualified name
, qualified :: Bool
, hlintOpts :: [String]
} deriving (Show)
-- | A default 'Options'.
defaultOptions :: Options
defaultOptions = Options {
outputStyle = PlainStyle
, hlintOpts = []
, ghcProgram = "ghc"
, cabalProgram = "cabal"
, ghcUserOptions= []
, operators = False
, detailed = False
, qualified = False
, lineSeparator = LineSeparator "\0"
}
----------------------------------------------------------------
-- | The environment where this library is used.
data Cradle = Cradle {
-- | The directory where this library is executed.
cradleCurrentDir :: FilePath
-- | The project root directory.
, cradleRootDir :: FilePath
-- | Per-Project temporary directory
, cradleTempDir :: FilePath
-- | The file name of the found cabal file.
, cradleCabalFile :: Maybe FilePath
-- | Package database stack
, cradlePkgDbStack :: [GhcPkgDb]
} deriving (Eq, Show)
----------------------------------------------------------------
-- | GHC package database flags.
data GhcPkgDb = GlobalDb | UserDb | PackageDb String deriving (Eq, Show)
-- | A single GHC command line option.
type GHCOption = String
-- | An include directory for modules.
type IncludeDir = FilePath
-- | A package name.
type PackageBaseName = String
-- | A package version.
type PackageVersion = String
-- | A package id.
type PackageId = String
-- | A package's name, verson and id.
type Package = (PackageBaseName, PackageVersion, PackageId)
pkgName :: Package -> PackageBaseName
pkgName (n,_,_) = n
pkgVer :: Package -> PackageVersion
pkgVer (_,v,_) = v
pkgId :: Package -> PackageId
pkgId (_,_,i) = i
showPkg :: Package -> String
showPkg (n,v,_) = intercalate "-" [n,v]
showPkgId :: Package -> String
showPkgId (n,v,i) = intercalate "-" [n,v,i]
-- | Collection of packages
type PkgDb = (M.Map Package PackageConfig)
-- | Haskell expression.
type Expression = String
-- | Module name.
type ModuleString = String
-- | A Module
type Module = [String]
-- | Option information for GHC
data CompilerOptions = CompilerOptions {
ghcOptions :: [GHCOption] -- ^ Command line options
, includeDirs :: [IncludeDir] -- ^ Include directories for modules
, depPackages :: [Package] -- ^ Dependent package names
} deriving (Eq, Show)