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

299 lines
8.7 KiB
Haskell
Raw Normal View History

2015-04-02 23:15:12 +00:00
{-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveGeneric,
StandaloneDeriving, DefaultSignatures, FlexibleInstances #-}
2015-03-11 12:17:24 +00:00
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-deprecations #-}
module Language.Haskell.GhcMod.Types (
module Language.Haskell.GhcMod.Types
, ModuleName
, mkModuleName
, moduleNameString
) where
2010-04-30 09:36:31 +00:00
import Control.Monad.Trans.Control (MonadBaseControl)
import Control.Monad.Error (Error(..))
2015-04-02 23:15:12 +00:00
import qualified Control.Monad.IO.Class as MTL
import Control.Exception (Exception)
import Control.Applicative
import Data.Serialize
import Data.Version
import Data.List (intercalate)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Monoid
import Data.Maybe
import Data.Typeable (Typeable)
2015-03-15 19:48:55 +00:00
import Distribution.Helper
import Exception (ExceptionMonad)
2015-04-02 23:15:12 +00:00
#if __GLASGOW_HASKELL__ < 708
import qualified MonadUtils as GHC (MonadIO(..))
#endif
import GHC (ModuleName, moduleNameString, mkModuleName)
import PackageConfig (PackageConfig)
import GHC.Generics
-- | 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)
2014-08-12 16:08:28 +00:00
2015-04-02 23:15:12 +00:00
-- MonadUtils of GHC 7.6 or earlier defines its own MonadIO.
-- MonadUtils of GHC 7.8 or later imports MonadIO in Monad.Control.IO.Class.
#if __GLASGOW_HASKELL__ < 708
type MonadIOC m = (GHC.MonadIO m, MTL.MonadIO m)
#else
type MonadIOC m = (MTL.MonadIO m)
#endif
class MonadIOC m => MonadIO m where
2015-06-01 14:54:50 +00:00
liftIO :: IO a -> m a
2015-04-02 23:15:12 +00:00
2013-05-20 05:28:56 +00:00
-- | Output style.
2013-09-05 05:35:28 +00:00
data OutputStyle = LispStyle -- ^ S expression style.
| PlainStyle -- ^ Plain textstyle.
2014-10-22 22:53:41 +00:00
deriving (Show)
2012-02-14 01:21:48 +00:00
2013-09-05 05:35:28 +00:00
-- | The type for line separator. Historically, a Null string is used.
2014-10-22 22:53:41 +00:00
newtype LineSeparator = LineSeparator String deriving (Show)
2013-09-03 05:40:51 +00:00
2010-04-30 09:36:31 +00:00
data Options = Options {
2013-09-03 05:40:51 +00:00
outputStyle :: OutputStyle
-- | Line separator string.
, lineSeparator :: LineSeparator
-- | Verbosity
, logLevel :: GmLogLevel
-- | @ghc@ program name.
, ghcProgram :: FilePath
-- | @ghc-pkg@ program name.
, ghcPkgProgram :: FilePath
-- | @cabal@ program name.
, cabalProgram :: FilePath
2014-08-13 16:40:01 +00:00
-- | GHC command line options set on the @ghc-mod@ command line
, ghcUserOptions:: [GHCOption]
2013-09-05 05:35:28 +00:00
-- | If 'True', 'browse' also returns operators.
2013-09-03 05:40:51 +00:00
, operators :: Bool
2013-05-20 05:28:56 +00:00
-- | If 'True', 'browse' also returns types.
2013-09-03 05:40:51 +00:00
, detailed :: Bool
-- | If 'True', 'browse' will return fully qualified name
, qualified :: Bool
, hlintOpts :: [String]
2014-10-22 22:53:41 +00:00
} deriving (Show)
2012-02-27 02:23:56 +00:00
2013-05-20 05:28:56 +00:00
-- | A default 'Options'.
2012-02-27 02:23:56 +00:00
defaultOptions :: Options
defaultOptions = Options {
2015-06-01 14:54:50 +00:00
outputStyle = PlainStyle
, lineSeparator = LineSeparator "\0"
, logLevel = GmWarning
, ghcProgram = "ghc"
, ghcPkgProgram = "ghc-pkg"
, cabalProgram = "cabal"
, ghcUserOptions = []
, operators = False
, detailed = False
, qualified = False
, hlintOpts = []
2010-04-30 09:36:31 +00:00
}
2012-02-14 02:33:27 +00:00
----------------------------------------------------------------
2012-02-14 07:09:53 +00:00
2013-09-05 05:35:28 +00:00
-- | The environment where this library is used.
data Cradle = Cradle {
2013-09-05 05:35:28 +00:00
-- | The directory where this library is executed.
cradleCurrentDir :: FilePath
-- | The project root directory.
, cradleRootDir :: FilePath
-- | Per-Project temporary directory
, cradleTempDir :: FilePath
2013-09-05 05:35:28 +00:00
-- | The file name of the found cabal file.
, cradleCabalFile :: Maybe FilePath
-- | Package database stack
2015-06-01 14:54:50 +00:00
, cradlePkgDbStack :: [GhcPkgDb]
2013-03-05 01:22:33 +00:00
} deriving (Eq, Show)
----------------------------------------------------------------
-- | GHC package database flags.
data GhcPkgDb = GlobalDb | UserDb | PackageDb String deriving (Eq, Show)
-- | A single GHC command line option.
2015-06-01 14:54:50 +00:00
type GHCOption = String
-- | An include directory for modules.
type IncludeDir = FilePath
-- | A package name.
type PackageBaseName = String
-- | A package version.
2015-06-01 14:54:50 +00:00
type PackageVersion = String
-- | A package id.
2015-06-01 14:54:50 +00:00
type PackageId = String
-- | A package's name, verson and id.
2015-06-01 14:54:50 +00:00
type Package = (PackageBaseName, PackageVersion, PackageId)
pkgName :: Package -> PackageBaseName
2015-06-01 14:54:50 +00:00
pkgName (n, _, _) = n
pkgVer :: Package -> PackageVersion
2015-06-01 14:54:50 +00:00
pkgVer (_, v, _) = v
pkgId :: Package -> PackageId
2015-06-01 14:54:50 +00:00
pkgId (_, _, i) = i
showPkg :: Package -> String
2015-06-01 14:54:50 +00:00
showPkg (n, v, _) = intercalate "-" [n, v]
showPkgId :: Package -> String
2015-06-01 14:54:50 +00:00
showPkgId (n, v, i) = intercalate "-" [n, v, i]
-- | Haskell expression.
type Expression = String
-- | Module name.
type ModuleString = String
2015-06-01 14:54:50 +00:00
data GmLogLevel =
GmSilent
| GmPanic
| GmException
| GmError
| GmWarning
| GmInfo
| GmDebug
deriving (Eq, Ord, Enum, Bounded, Show, Read)
-- | Collection of packages
type PkgDb = (Map Package PackageConfig)
data GmModuleGraph = GmModuleGraph {
2015-06-01 14:54:50 +00:00
gmgGraph :: Map ModulePath (Set ModulePath)
} deriving (Eq, Ord, Show, Read, Generic, Typeable)
instance Serialize GmModuleGraph where
2015-06-01 14:54:50 +00:00
put GmModuleGraph {..} = put (mpim, graph)
where
mpim :: Map ModulePath Integer
mpim = Map.fromList $ Map.keys gmgGraph `zip` [0..]
graph :: Map Integer (Set Integer)
graph = Map.map (Set.map mpToInt) $ Map.mapKeys mpToInt gmgGraph
mpToInt :: ModulePath -> Integer
mpToInt mp = fromJust $ Map.lookup mp mpim
get = do
(mpim :: Map ModulePath Integer, graph :: Map Integer (Set Integer)) <- get
let impm = swapMap mpim
intToMp i = fromJust $ Map.lookup i impm
mpGraph :: Map ModulePath (Set ModulePath)
mpGraph = Map.map (Set.map intToMp) $ Map.mapKeys intToMp graph
return $ GmModuleGraph mpGraph
where
swapMap :: (Ord k, Ord v) => Map k v -> Map v k
swapMap = Map.fromList . map (\(x, y) -> (y, x)) . Map.toList
instance Monoid GmModuleGraph where
2015-06-01 14:54:50 +00:00
mempty = GmModuleGraph mempty
mappend (GmModuleGraph a) (GmModuleGraph a') =
GmModuleGraph (Map.unionWith Set.union a a')
data GmComponentType = GMCRaw
| GMCResolved
data GmComponent (t :: GmComponentType) eps = GmComponent {
2015-06-01 14:54:50 +00:00
gmcHomeModuleGraph :: GmModuleGraph
, gmcName :: ChComponentName
, gmcGhcOpts :: [GHCOption]
, gmcGhcPkgOpts :: [GHCOption]
, gmcGhcSrcOpts :: [GHCOption]
, gmcGhcLangOpts :: [GHCOption]
, gmcRawEntrypoints :: ChEntrypoint
, gmcEntrypoints :: eps
, gmcSourceDirs :: [FilePath]
} deriving (Eq, Ord, Show, Read, Generic, Functor)
instance Serialize eps => Serialize (GmComponent t eps)
data ModulePath = ModulePath { mpModule :: ModuleName, mpPath :: FilePath }
2015-06-01 14:54:50 +00:00
deriving (Eq, Ord, Show, Read, Generic, Typeable)
instance Serialize ModulePath
instance Serialize ModuleName where
2015-06-01 14:54:50 +00:00
get = mkModuleName <$> get
put mn = put (moduleNameString mn)
instance Show ModuleName where
2015-06-01 14:54:50 +00:00
show mn = "ModuleName " ++ show (moduleNameString mn)
instance Read ModuleName where
2015-06-01 14:54:50 +00:00
readsPrec d =
readParen
(d > app_prec)
(\r' -> [ (mkModuleName m, t)
| ("ModuleName", s) <- lex r'
, (m, t) <- readsPrec (app_prec + 1) s
])
where
app_prec = 10
data GhcModError
2015-06-01 14:54:50 +00:00
= GMENoMsg
-- ^ Unknown error
2015-06-01 14:54:50 +00:00
| GMEString String
-- ^ Some Error with a message. These are produced mostly by
-- 'fail' calls on GhcModT.
2015-06-01 14:54:50 +00:00
| GMECabalConfigure GhcModError
-- ^ Configuring a cabal project failed.
2015-06-01 14:54:50 +00:00
| GMECabalFlags GhcModError
-- ^ Retrieval of the cabal configuration flags failed.
2015-06-01 14:54:50 +00:00
| GMECabalComponent ChComponentName
-- ^ Cabal component could not be found
2015-06-01 14:54:50 +00:00
| GMECabalCompAssignment [(Either FilePath ModuleName, Set ChComponentName)]
-- ^ Could not find a consistent component assignment for modules
2015-06-01 14:54:50 +00:00
| GMEProcess String [String] (Either (String, String, Int) GhcModError)
-- ^ Launching an operating system process failed. Fields in
-- order: command, arguments, (stdout, stderr, exitcode)
2015-06-01 14:54:50 +00:00
| GMENoCabalFile
-- ^ No cabal file found.
2015-06-01 14:54:50 +00:00
| GMETooManyCabalFiles [FilePath]
-- ^ Too many cabal files found.
2015-06-01 14:54:50 +00:00
| GMECabalStateFile GMConfigStateFileError
-- ^ Reading Cabal's state configuration file falied somehow.
deriving (Eq,Show,Typeable)
instance Error GhcModError where
2015-06-01 14:54:50 +00:00
noMsg = GMENoMsg
strMsg = GMEString
instance Exception GhcModError
data GMConfigStateFileError
2015-06-01 14:54:50 +00:00
= GMConfigStateFileNoHeader
| GMConfigStateFileBadHeader
| GMConfigStateFileNoParse
| GMConfigStateFileMissing
-- | GMConfigStateFileBadVersion PackageIdentifier PackageIdentifier (Either ConfigStateFileError LocalBuildInfo)
deriving (Eq, Show, Read, Typeable)
deriving instance Generic Version
instance Serialize Version
instance Serialize Programs
instance Serialize ChModuleName
instance Serialize ChComponentName
instance Serialize ChEntrypoint