Reorganize module namespace
- Remove Language.Haskell prefix from all modules - Move 'GHCMod.*' to 'GhcMod.Exe' - Move 'GhcModExe' to 'GhcMod.Exe'
This commit is contained in:
parent
84524dbd86
commit
35690941aa
42
GhcMod.hs
42
GhcMod.hs
@ -69,24 +69,24 @@ module GhcMod (
|
|||||||
, unloadMappedFile
|
, unloadMappedFile
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import GhcModExe.Boot
|
import GhcMod.Exe.Boot
|
||||||
import GhcModExe.Browse
|
import GhcMod.Exe.Browse
|
||||||
import GhcModExe.CaseSplit
|
import GhcMod.Exe.CaseSplit
|
||||||
import GhcModExe.Check
|
import GhcMod.Exe.Check
|
||||||
import GhcModExe.Debug
|
import GhcMod.Exe.Debug
|
||||||
import GhcModExe.FillSig
|
import GhcMod.Exe.FillSig
|
||||||
import GhcModExe.Find
|
import GhcMod.Exe.Find
|
||||||
import GhcModExe.Flag
|
import GhcMod.Exe.Flag
|
||||||
import GhcModExe.Info
|
import GhcMod.Exe.Info
|
||||||
import GhcModExe.Lang
|
import GhcMod.Exe.Lang
|
||||||
import GhcModExe.Lint
|
import GhcMod.Exe.Lint
|
||||||
import GhcModExe.Modules
|
import GhcMod.Exe.Modules
|
||||||
import GhcModExe.PkgDoc
|
import GhcMod.Exe.PkgDoc
|
||||||
import GhcModExe.Test
|
import GhcMod.Exe.Test
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.FileMapping
|
import GhcMod.FileMapping
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
import Language.Haskell.GhcMod.Target
|
import GhcMod.Target
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
|
@ -1,14 +1,14 @@
|
|||||||
module GhcModExe.Boot where
|
module GhcMod.Exe.Boot where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import GhcModExe.Browse
|
import GhcMod.Exe.Browse
|
||||||
import GhcModExe.Flag
|
import GhcMod.Exe.Flag
|
||||||
import GhcModExe.Lang
|
import GhcMod.Exe.Lang
|
||||||
import GhcModExe.Modules
|
import GhcMod.Exe.Modules
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Types (defaultBrowseOpts)
|
import GhcMod.Types (defaultBrowseOpts)
|
||||||
|
|
||||||
-- | Printing necessary information for front-end booting.
|
-- | Printing necessary information for front-end booting.
|
||||||
boot :: IOish m => GhcModT m String
|
boot :: IOish m => GhcModT m String
|
@ -1,5 +1,5 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module GhcModExe.Browse (
|
module GhcMod.Exe.Browse (
|
||||||
browse,
|
browse,
|
||||||
BrowseOpts(..)
|
BrowseOpts(..)
|
||||||
) where
|
) where
|
||||||
@ -14,12 +14,12 @@ import FastString
|
|||||||
import GHC
|
import GHC
|
||||||
import HscTypes
|
import HscTypes
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.Doc (showPage, styleUnqualified)
|
import GhcMod.Doc (showPage, styleUnqualified)
|
||||||
import Language.Haskell.GhcMod.Gap as Gap
|
import GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Name (getOccString)
|
import Name (getOccString)
|
||||||
import Outputable
|
import Outputable
|
||||||
import TyCon (isAlgTyCon)
|
import TyCon (isAlgTyCon)
|
@ -1,6 +1,6 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module GhcModExe.CaseSplit (
|
module GhcMod.Exe.CaseSplit (
|
||||||
splits
|
splits
|
||||||
) where
|
) where
|
||||||
|
|
||||||
@ -19,16 +19,16 @@ import qualified TyCon as Ty
|
|||||||
import qualified Type as Ty
|
import qualified Type as Ty
|
||||||
import Exception
|
import Exception
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.SrcUtils
|
import GhcMod.SrcUtils
|
||||||
import Language.Haskell.GhcMod.Doc
|
import GhcMod.Doc
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils (withMappedFile)
|
import GhcMod.Utils (withMappedFile)
|
||||||
import Language.Haskell.GhcMod.FileMapping (fileModSummaryWithMapping)
|
import GhcMod.FileMapping (fileModSummaryWithMapping)
|
||||||
import Control.DeepSeq
|
import Control.DeepSeq
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
@ -1,4 +1,4 @@
|
|||||||
module GhcModExe.Check (
|
module GhcMod.Exe.Check (
|
||||||
checkSyntax
|
checkSyntax
|
||||||
, check
|
, check
|
||||||
, expandTemplate
|
, expandTemplate
|
||||||
@ -7,10 +7,10 @@ module GhcModExe.Check (
|
|||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Prelude
|
import Prelude
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Logger
|
import GhcMod.Logger
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
@ -1,4 +1,4 @@
|
|||||||
module GhcModExe.Debug (debugInfo, rootInfo, componentInfo) where
|
module GhcMod.Exe.Debug (debugInfo, rootInfo, componentInfo) where
|
||||||
|
|
||||||
import Control.Arrow (first)
|
import Control.Arrow (first)
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
@ -11,15 +11,15 @@ import Data.Version
|
|||||||
import Data.List.Split
|
import Data.List.Split
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
|
||||||
import GhcModExe.Internal
|
import GhcMod.Exe.Internal
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
import Language.Haskell.GhcMod.Pretty
|
import GhcMod.Pretty
|
||||||
import Language.Haskell.GhcMod.Stack
|
import GhcMod.Stack
|
||||||
import Language.Haskell.GhcMod.Target
|
import GhcMod.Target
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils
|
import GhcMod.Utils
|
||||||
|
|
||||||
import Paths_ghc_mod (version)
|
import Paths_ghc_mod (version)
|
||||||
|
|
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE CPP, MultiParamTypeClasses, FunctionalDependencies #-}
|
{-# LANGUAGE CPP, MultiParamTypeClasses, FunctionalDependencies #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
|
||||||
module GhcModExe.FillSig (
|
module GhcMod.Exe.FillSig (
|
||||||
sig
|
sig
|
||||||
, refine
|
, refine
|
||||||
, auto
|
, auto
|
||||||
@ -30,16 +30,16 @@ import qualified HsPat as Ty
|
|||||||
import qualified Language.Haskell.Exts as HE
|
import qualified Language.Haskell.Exts as HE
|
||||||
import Djinn.GHC
|
import Djinn.GHC
|
||||||
|
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.SrcUtils
|
import GhcMod.SrcUtils
|
||||||
import Language.Haskell.GhcMod.Logging (gmLog)
|
import GhcMod.Logging (gmLog)
|
||||||
import Language.Haskell.GhcMod.Pretty (showToDoc)
|
import GhcMod.Pretty (showToDoc)
|
||||||
import Language.Haskell.GhcMod.Doc
|
import GhcMod.Doc
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.FileMapping (fileModSummaryWithMapping)
|
import GhcMod.FileMapping (fileModSummaryWithMapping)
|
||||||
|
|
||||||
#if __GLASGOW_HASKELL__ >= 710
|
#if __GLASGOW_HASKELL__ >= 710
|
||||||
import GHC (unLoc)
|
import GHC (unLoc)
|
@ -1,6 +1,6 @@
|
|||||||
{-# LANGUAGE CPP, BangPatterns, TupleSections, DeriveGeneric #-}
|
{-# LANGUAGE CPP, BangPatterns, TupleSections, DeriveGeneric #-}
|
||||||
|
|
||||||
module GhcModExe.Find
|
module GhcMod.Exe.Find
|
||||||
( Symbol
|
( Symbol
|
||||||
, SymbolDb
|
, SymbolDb
|
||||||
, loadSymbolDb
|
, loadSymbolDb
|
||||||
@ -22,14 +22,14 @@ import OccName
|
|||||||
import HscTypes
|
import HscTypes
|
||||||
import Exception
|
import Exception
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.Gap
|
import GhcMod.Gap
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils
|
import GhcMod.Utils
|
||||||
import Language.Haskell.GhcMod.World
|
import GhcMod.World
|
||||||
import Language.Haskell.GhcMod.LightGhc
|
import GhcMod.LightGhc
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.DeepSeq
|
import Control.DeepSeq
|
||||||
@ -53,7 +53,7 @@ import Data.Map (Map)
|
|||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.Set (Set)
|
import Data.Set (Set)
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
9
GhcMod/Exe/Flag.hs
Normal file
9
GhcMod/Exe/Flag.hs
Normal file
@ -0,0 +1,9 @@
|
|||||||
|
module GhcMod.Exe.Flag where
|
||||||
|
|
||||||
|
import qualified GhcMod.Gap as Gap
|
||||||
|
import GhcMod.Convert
|
||||||
|
import GhcMod.Monad
|
||||||
|
|
||||||
|
-- | Listing of GHC flags, same as @ghc@\'s @--show-options@ with @ghc >= 7.10@.
|
||||||
|
flags :: IOish m => GhcModT m String
|
||||||
|
flags = convert' Gap.ghcCmdOptions
|
@ -1,4 +1,4 @@
|
|||||||
module GhcModExe.Info (
|
module GhcMod.Exe.Info (
|
||||||
info
|
info
|
||||||
, types
|
, types
|
||||||
) where
|
) where
|
||||||
@ -11,17 +11,17 @@ import GHC (GhcMonad, SrcSpan)
|
|||||||
import Prelude
|
import Prelude
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
|
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.Doc
|
import GhcMod.Doc
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
import Language.Haskell.GhcMod.Gap
|
import GhcMod.Gap
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.SrcUtils
|
import GhcMod.SrcUtils
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils (mkRevRedirMapFunc)
|
import GhcMod.Utils (mkRevRedirMapFunc)
|
||||||
import Language.Haskell.GhcMod.FileMapping (fileModSummaryWithMapping)
|
import GhcMod.FileMapping (fileModSummaryWithMapping)
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
@ -1,6 +1,6 @@
|
|||||||
-- | Low level access to the ghc-mod library.
|
-- | Low level access to the ghc-mod library.
|
||||||
|
|
||||||
module GhcModExe.Internal (
|
module GhcMod.Exe.Internal (
|
||||||
-- * Types
|
-- * Types
|
||||||
GHCOption
|
GHCOption
|
||||||
, IncludeDir
|
, IncludeDir
|
||||||
@ -51,22 +51,22 @@ module GhcModExe.Internal (
|
|||||||
, GHandler(..)
|
, GHandler(..)
|
||||||
, gcatches
|
, gcatches
|
||||||
-- * FileMapping
|
-- * FileMapping
|
||||||
, module Language.Haskell.GhcMod.FileMapping
|
, module GhcMod.FileMapping
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import GHC.Paths (libdir)
|
import GHC.Paths (libdir)
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Target
|
import GhcMod.Target
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import Language.Haskell.GhcMod.Logger
|
import GhcMod.Logger
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils
|
import GhcMod.Utils
|
||||||
import Language.Haskell.GhcMod.World
|
import GhcMod.World
|
||||||
import Language.Haskell.GhcMod.CabalHelper
|
import GhcMod.CabalHelper
|
||||||
import Language.Haskell.GhcMod.FileMapping
|
import GhcMod.FileMapping
|
||||||
|
|
||||||
-- | Obtaining the directory for ghc system libraries.
|
-- | Obtaining the directory for ghc system libraries.
|
||||||
ghcLibDir :: FilePath
|
ghcLibDir :: FilePath
|
@ -1,8 +1,8 @@
|
|||||||
module GhcModExe.Lang where
|
module GhcMod.Exe.Lang where
|
||||||
|
|
||||||
import DynFlags (supportedLanguagesAndExtensions)
|
import DynFlags (supportedLanguagesAndExtensions)
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
|
|
||||||
-- | Listing language extensions.
|
-- | Listing language extensions.
|
||||||
|
|
@ -1,14 +1,14 @@
|
|||||||
module GhcModExe.Lint where
|
module GhcMod.Exe.Lint where
|
||||||
|
|
||||||
import Exception (ghandle)
|
import Exception (ghandle)
|
||||||
import Control.Exception (SomeException(..))
|
import Control.Exception (SomeException(..))
|
||||||
import Language.Haskell.GhcMod.Logger (checkErrorPrefix)
|
import GhcMod.Logger (checkErrorPrefix)
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.HLint3
|
import Language.Haskell.HLint3
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Utils (withMappedFile)
|
import GhcMod.Utils (withMappedFile)
|
||||||
import Language.Haskell.Exts.SrcLoc (SrcSpan(..))
|
import Language.Haskell.Exts.SrcLoc (SrcSpan(..))
|
||||||
|
|
||||||
-- | Checking syntax of a target file using hlint.
|
-- | Checking syntax of a target file using hlint.
|
@ -1,11 +1,11 @@
|
|||||||
module GhcModExe.Modules (modules) where
|
module GhcMod.Exe.Modules (modules) where
|
||||||
|
|
||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
import Data.List
|
import Data.List
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Gap ( listVisibleModuleNames
|
import GhcMod.Gap ( listVisibleModuleNames
|
||||||
, lookupModulePackageInAllPackages
|
, lookupModulePackageInAllPackages
|
||||||
)
|
)
|
||||||
|
|
@ -1,9 +1,9 @@
|
|||||||
module GhcModExe.PkgDoc (pkgDoc) where
|
module GhcMod.Exe.PkgDoc (pkgDoc) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.GhcPkg
|
import GhcMod.GhcPkg
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Prelude
|
import Prelude
|
@ -1,4 +1,4 @@
|
|||||||
module GhcModExe.Test where
|
module GhcMod.Exe.Test where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.List
|
import Data.List
|
||||||
@ -6,9 +6,9 @@ import System.FilePath
|
|||||||
import System.Directory
|
import System.Directory
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
|
|
||||||
import GHC
|
import GHC
|
||||||
import GHC.Exception
|
import GHC.Exception
|
@ -1,9 +0,0 @@
|
|||||||
module GhcModExe.Flag where
|
|
||||||
|
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
|
||||||
import Language.Haskell.GhcMod.Convert
|
|
||||||
import Language.Haskell.GhcMod.Monad
|
|
||||||
|
|
||||||
-- | Listing of GHC flags, same as @ghc@\'s @--show-options@ with @ghc >= 7.10@.
|
|
||||||
flags :: IOish m => GhcModT m String
|
|
||||||
flags = convert' Gap.ghcCmdOptions
|
|
@ -1,7 +1,7 @@
|
|||||||
import Criterion.Main
|
import Criterion.Main
|
||||||
import Language.Haskell.GhcMod.Target
|
import GhcMod.Target
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Dir
|
import Dir
|
||||||
import System.IO.Temp
|
import System.IO.Temp
|
||||||
import System.Process hiding (env)
|
import System.Process hiding (env)
|
||||||
|
@ -15,7 +15,7 @@
|
|||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module Language.Haskell.GhcMod.CabalHelper
|
module GhcMod.CabalHelper
|
||||||
( getComponents
|
( getComponents
|
||||||
, getGhcMergedPkgOptions
|
, getGhcMergedPkgOptions
|
||||||
, getCabalPackageDbStack
|
, getCabalPackageDbStack
|
||||||
@ -34,15 +34,15 @@ import Data.Binary (Binary)
|
|||||||
import Data.Traversable
|
import Data.Traversable
|
||||||
import Distribution.Helper hiding (Programs(..))
|
import Distribution.Helper hiding (Programs(..))
|
||||||
import qualified Distribution.Helper as CH
|
import qualified Distribution.Helper as CH
|
||||||
import qualified Language.Haskell.GhcMod.Types as T
|
import qualified GhcMod.Types as T
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Utils
|
import GhcMod.Utils
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
import Language.Haskell.GhcMod.CustomPackageDb
|
import GhcMod.CustomPackageDb
|
||||||
import Language.Haskell.GhcMod.Stack
|
import GhcMod.Stack
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Process
|
import System.Process
|
||||||
import System.Exit
|
import System.Exit
|
@ -14,9 +14,9 @@
|
|||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
{-# LANGUAGE CPP, OverloadedStrings #-}
|
{-# LANGUAGE CPP, OverloadedStrings #-}
|
||||||
module Language.Haskell.GhcMod.Caching (
|
module GhcMod.Caching (
|
||||||
module Language.Haskell.GhcMod.Caching
|
module GhcMod.Caching
|
||||||
, module Language.Haskell.GhcMod.Caching.Types
|
, module GhcMod.Caching.Types
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Arrow (first)
|
import Control.Arrow (first)
|
||||||
@ -38,9 +38,9 @@ import Utils (TimedFile(..), timeMaybe, mightExist)
|
|||||||
import Paths_ghc_mod (version)
|
import Paths_ghc_mod (version)
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Caching.Types
|
import GhcMod.Caching.Types
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
|
|
||||||
-- | Cache a MonadIO action with proper invalidation.
|
-- | Cache a MonadIO action with proper invalidation.
|
||||||
cached :: forall m a d. (Gm m, MonadIO m, Binary a, Eq d, Binary d, Show d)
|
cached :: forall m a d. (Gm m, MonadIO m, Binary a, Eq d, Binary d, Show d)
|
@ -13,7 +13,7 @@
|
|||||||
--
|
--
|
||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
module Language.Haskell.GhcMod.Caching.Types where
|
module GhcMod.Caching.Types where
|
||||||
|
|
||||||
import Utils
|
import Utils
|
||||||
import Data.Label
|
import Data.Label
|
@ -1,9 +1,9 @@
|
|||||||
{-# LANGUAGE CPP, FlexibleInstances, FlexibleContexts #-}
|
{-# LANGUAGE CPP, FlexibleInstances, FlexibleContexts #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Convert (convert, convert', emptyResult, whenFound, whenFound') where
|
module GhcMod.Convert (convert, convert', emptyResult, whenFound, whenFound') where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Prelude
|
import Prelude
|
@ -1,5 +1,5 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module Language.Haskell.GhcMod.Cradle
|
module GhcMod.Cradle
|
||||||
( findCradle
|
( findCradle
|
||||||
, findCradle'
|
, findCradle'
|
||||||
, findCradleNoLog
|
, findCradleNoLog
|
||||||
@ -10,13 +10,13 @@ module Language.Haskell.GhcMod.Cradle
|
|||||||
, plainCradle
|
, plainCradle
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils
|
import GhcMod.Utils
|
||||||
import Language.Haskell.GhcMod.Stack
|
import GhcMod.Stack
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
|
|
||||||
import Safe
|
import Safe
|
||||||
import Control.Applicative
|
import Control.Applicative
|
@ -13,16 +13,16 @@
|
|||||||
--
|
--
|
||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
module Language.Haskell.GhcMod.CustomPackageDb where
|
module GhcMod.CustomPackageDb where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Category ((.))
|
import Control.Category ((.))
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Traversable
|
import Data.Traversable
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Prelude hiding ((.))
|
import Prelude hiding ((.))
|
||||||
|
|
||||||
parseCustomPackageDb :: String -> [GhcPkgDb]
|
parseCustomPackageDb :: String -> [GhcPkgDb]
|
@ -14,7 +14,7 @@
|
|||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
{-# LANGUAGE CPP, RankNTypes #-}
|
{-# LANGUAGE CPP, RankNTypes #-}
|
||||||
module Language.Haskell.GhcMod.DebugLogger where
|
module GhcMod.DebugLogger where
|
||||||
|
|
||||||
-- (c) The University of Glasgow 2005
|
-- (c) The University of Glasgow 2005
|
||||||
--
|
--
|
||||||
@ -57,8 +57,8 @@ import Outputable (SDoc, PprStyle, runSDoc, initSDocContext, blankLine)
|
|||||||
import qualified Outputable
|
import qualified Outputable
|
||||||
import ErrUtils
|
import ErrUtils
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import Language.Haskell.GhcMod.Gap
|
import GhcMod.Gap
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
debugLogAction :: (String -> IO ()) -> GmLogAction
|
debugLogAction :: (String -> IO ()) -> GmLogAction
|
@ -1,7 +1,7 @@
|
|||||||
module Language.Haskell.GhcMod.Doc where
|
module GhcMod.Doc where
|
||||||
|
|
||||||
import GHC
|
import GHC
|
||||||
import Language.Haskell.GhcMod.Gap (withStyle, showDocWith)
|
import GhcMod.Gap (withStyle, showDocWith)
|
||||||
import Outputable
|
import Outputable
|
||||||
import Pretty (Mode(..))
|
import Pretty (Mode(..))
|
||||||
|
|
@ -1,16 +1,16 @@
|
|||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.DynFlags where
|
module GhcMod.DynFlags where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import GHC
|
import GHC
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
import GHC.Paths (libdir)
|
import GHC.Paths (libdir)
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.DebugLogger
|
import GhcMod.DebugLogger
|
||||||
import Language.Haskell.GhcMod.DynFlagsTH
|
import GhcMod.DynFlagsTH
|
||||||
import System.IO.Unsafe (unsafePerformIO)
|
import System.IO.Unsafe (unsafePerformIO)
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
@ -15,7 +15,7 @@
|
|||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
{-# LANGUAGE CPP, TemplateHaskell #-}
|
{-# LANGUAGE CPP, TemplateHaskell #-}
|
||||||
module Language.Haskell.GhcMod.DynFlagsTH where
|
module GhcMod.DynFlagsTH where
|
||||||
|
|
||||||
import Language.Haskell.TH
|
import Language.Haskell.TH
|
||||||
import Language.Haskell.TH.Syntax
|
import Language.Haskell.TH.Syntax
|
@ -15,7 +15,7 @@
|
|||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
{-# LANGUAGE ExistentialQuantification #-}
|
{-# LANGUAGE ExistentialQuantification #-}
|
||||||
module Language.Haskell.GhcMod.Error (
|
module GhcMod.Error (
|
||||||
GhcModError(..)
|
GhcModError(..)
|
||||||
, GmError
|
, GmError
|
||||||
, gmeDoc
|
, gmeDoc
|
||||||
@ -47,8 +47,8 @@ import Pretty
|
|||||||
import Config (cProjectVersion, cHostPlatformString)
|
import Config (cProjectVersion, cHostPlatformString)
|
||||||
import Paths_ghc_mod (version)
|
import Paths_ghc_mod (version)
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Pretty
|
import GhcMod.Pretty
|
||||||
|
|
||||||
type GmError m = MonadError GhcModError m
|
type GmError m = MonadError GhcModError m
|
||||||
|
|
@ -1,4 +1,4 @@
|
|||||||
module Language.Haskell.GhcMod.FileMapping
|
module GhcMod.FileMapping
|
||||||
( loadMappedFile
|
( loadMappedFile
|
||||||
, loadMappedFileSource
|
, loadMappedFileSource
|
||||||
, unloadMappedFile
|
, unloadMappedFile
|
||||||
@ -6,11 +6,11 @@ module Language.Haskell.GhcMod.FileMapping
|
|||||||
, fileModSummaryWithMapping
|
, fileModSummaryWithMapping
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Gap
|
import GhcMod.Gap
|
||||||
import Language.Haskell.GhcMod.HomeModuleGraph
|
import GhcMod.HomeModuleGraph
|
||||||
import Language.Haskell.GhcMod.Utils
|
import GhcMod.Utils
|
||||||
|
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.FilePath
|
import System.FilePath
|
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP, ScopedTypeVariables, RankNTypes #-}
|
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP, ScopedTypeVariables, RankNTypes #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Gap (
|
module GhcMod.Gap (
|
||||||
Language.Haskell.GhcMod.Gap.ClsInst
|
GhcMod.Gap.ClsInst
|
||||||
, mkTarget
|
, mkTarget
|
||||||
, withStyle
|
, withStyle
|
||||||
, GmLogAction
|
, GmLogAction
|
||||||
@ -44,7 +44,7 @@ module Language.Haskell.GhcMod.Gap (
|
|||||||
, listVisibleModuleNames
|
, listVisibleModuleNames
|
||||||
, listVisibleModules
|
, listVisibleModules
|
||||||
, lookupModulePackageInAllPackages
|
, lookupModulePackageInAllPackages
|
||||||
, Language.Haskell.GhcMod.Gap.isSynTyCon
|
, GhcMod.Gap.isSynTyCon
|
||||||
, parseModuleHeader
|
, parseModuleHeader
|
||||||
, mkErrStyle'
|
, mkErrStyle'
|
||||||
, everythingStagedWithContext
|
, everythingStagedWithContext
|
||||||
@ -139,7 +139,7 @@ import Packages
|
|||||||
import Data.Generics (GenericQ, extQ, gmapQ)
|
import Data.Generics (GenericQ, extQ, gmapQ)
|
||||||
import GHC.SYB.Utils (Stage(..))
|
import GHC.SYB.Utils (Stage(..))
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types (Expression(..))
|
import GhcMod.Types (Expression(..))
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
@ -1,5 +1,5 @@
|
|||||||
{-# LANGUAGE BangPatterns, ScopedTypeVariables, TupleSections #-}
|
{-# LANGUAGE BangPatterns, ScopedTypeVariables, TupleSections #-}
|
||||||
module Language.Haskell.GhcMod.GhcPkg (
|
module GhcMod.GhcPkg (
|
||||||
ghcPkgDbOpt
|
ghcPkgDbOpt
|
||||||
, ghcPkgDbStackOpts
|
, ghcPkgDbStackOpts
|
||||||
, ghcDbStackOpts
|
, ghcDbStackOpts
|
||||||
@ -18,12 +18,12 @@ import System.Directory (doesDirectoryExist, getAppUserDataDirectory)
|
|||||||
import System.FilePath ((</>))
|
import System.FilePath ((</>))
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.CabalHelper
|
import GhcMod.CabalHelper
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Language.Haskell.GhcMod.CustomPackageDb
|
import GhcMod.CustomPackageDb
|
||||||
import Language.Haskell.GhcMod.Stack
|
import GhcMod.Stack
|
||||||
|
|
||||||
ghcVersion :: Int
|
ghcVersion :: Int
|
||||||
ghcVersion = read cProjectVersionInt
|
ghcVersion = read cProjectVersionInt
|
@ -15,7 +15,7 @@
|
|||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
{-# LANGUAGE ScopedTypeVariables, RecordWildCards #-}
|
{-# LANGUAGE ScopedTypeVariables, RecordWildCards #-}
|
||||||
module Language.Haskell.GhcMod.HomeModuleGraph (
|
module GhcMod.HomeModuleGraph (
|
||||||
GmModuleGraph(..)
|
GmModuleGraph(..)
|
||||||
, ModulePath(..)
|
, ModulePath(..)
|
||||||
, mkFileMap
|
, mkFileMap
|
||||||
@ -58,12 +58,12 @@ import System.Directory
|
|||||||
import System.IO
|
import System.IO
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Logger
|
import GhcMod.Logger
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils (withMappedFile)
|
import GhcMod.Utils (withMappedFile)
|
||||||
import Language.Haskell.GhcMod.Gap (parseModuleHeader)
|
import GhcMod.Gap (parseModuleHeader)
|
||||||
|
|
||||||
-- | Turn module graph into a graphviz dot file
|
-- | Turn module graph into a graphviz dot file
|
||||||
--
|
--
|
@ -1,4 +1,4 @@
|
|||||||
module Language.Haskell.GhcMod.LightGhc where
|
module GhcMod.LightGhc where
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.Reader (runReaderT)
|
import Control.Monad.Reader (runReaderT)
|
||||||
@ -12,10 +12,10 @@ import DynFlags
|
|||||||
import HscMain
|
import HscMain
|
||||||
import HscTypes
|
import HscTypes
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
|
|
||||||
-- We have to be more careful about tearing down 'HscEnv's since GHC 8 added an
|
-- We have to be more careful about tearing down 'HscEnv's since GHC 8 added an
|
||||||
-- out of process GHCI server which has to be shutdown.
|
-- out of process GHCI server which has to be shutdown.
|
@ -1,6 +1,6 @@
|
|||||||
{-# LANGUAGE CPP, RankNTypes #-}
|
{-# LANGUAGE CPP, RankNTypes #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Logger (
|
module GhcMod.Logger (
|
||||||
withLogger
|
withLogger
|
||||||
, withLogger'
|
, withLogger'
|
||||||
, checkErrorPrefix
|
, checkErrorPrefix
|
||||||
@ -27,14 +27,14 @@ import Bag
|
|||||||
import SrcLoc
|
import SrcLoc
|
||||||
import FastString
|
import FastString
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Convert
|
import GhcMod.Convert
|
||||||
import Language.Haskell.GhcMod.Doc (showPage)
|
import GhcMod.Doc (showPage)
|
||||||
import Language.Haskell.GhcMod.DynFlags (withDynFlags)
|
import GhcMod.DynFlags (withDynFlags)
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import Language.Haskell.GhcMod.Pretty
|
import GhcMod.Pretty
|
||||||
import Language.Haskell.GhcMod.Utils (mkRevRedirMapFunc)
|
import GhcMod.Utils (mkRevRedirMapFunc)
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
type Builder = [String] -> [String]
|
type Builder = [String] -> [String]
|
@ -16,9 +16,9 @@
|
|||||||
|
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Logging (
|
module GhcMod.Logging (
|
||||||
module Language.Haskell.GhcMod.Logging
|
module GhcMod.Logging
|
||||||
, module Language.Haskell.GhcMod.Pretty
|
, module GhcMod.Pretty
|
||||||
, GmLogLevel(..)
|
, GmLogLevel(..)
|
||||||
, module Data.Monoid
|
, module Data.Monoid
|
||||||
, module Pretty
|
, module Pretty
|
||||||
@ -37,10 +37,10 @@ import Prelude
|
|||||||
|
|
||||||
import Pretty hiding (style, (<>))
|
import Pretty hiding (style, (<>))
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Pretty
|
import GhcMod.Pretty
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
|
|
||||||
gmSetLogLevel :: GmLog m => GmLogLevel -> m ()
|
gmSetLogLevel :: GmLog m => GmLogLevel -> m ()
|
||||||
gmSetLogLevel level =
|
gmSetLogLevel level =
|
@ -15,7 +15,7 @@
|
|||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module Language.Haskell.GhcMod.Monad (
|
module GhcMod.Monad (
|
||||||
runGmOutT
|
runGmOutT
|
||||||
, runGmOutT'
|
, runGmOutT'
|
||||||
, runGhcModT
|
, runGhcModT
|
||||||
@ -27,16 +27,16 @@ module Language.Haskell.GhcMod.Monad (
|
|||||||
, runGmPkgGhc
|
, runGmPkgGhc
|
||||||
, withGhcModEnv
|
, withGhcModEnv
|
||||||
, withGhcModEnv'
|
, withGhcModEnv'
|
||||||
, module Language.Haskell.GhcMod.Monad.Types
|
, module GhcMod.Monad.Types
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.Target
|
import GhcMod.Target
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
|
|
||||||
import Control.Arrow (first)
|
import Control.Arrow (first)
|
||||||
import Control.Applicative
|
import Control.Applicative
|
@ -17,10 +17,10 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
||||||
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
|
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Monad.Env where
|
module GhcMod.Monad.Env where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Newtypes
|
import GhcMod.Monad.Newtypes
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.Trans.Journal (JournalT)
|
import Control.Monad.Trans.Journal (JournalT)
|
@ -17,10 +17,10 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
||||||
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
|
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Monad.Log where
|
module GhcMod.Monad.Log where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Newtypes
|
import GhcMod.Monad.Newtypes
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.Trans.Journal (JournalT)
|
import Control.Monad.Trans.Journal (JournalT)
|
@ -18,11 +18,11 @@
|
|||||||
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies, UndecidableInstances #-}
|
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies, UndecidableInstances #-}
|
||||||
{-# LANGUAGE RankNTypes, FlexibleInstances #-}
|
{-# LANGUAGE RankNTypes, FlexibleInstances #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Monad.Newtypes where
|
module GhcMod.Monad.Newtypes where
|
||||||
|
|
||||||
#include "Compat.hs_h"
|
#include "Compat.hs_h"
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
|
|
||||||
import GHC
|
import GHC
|
||||||
|
|
@ -18,12 +18,12 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
|
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
module Language.Haskell.GhcMod.Monad.Orphans where
|
module GhcMod.Monad.Orphans where
|
||||||
|
|
||||||
#include "Compat.hs_h"
|
#include "Compat.hs_h"
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Newtypes
|
import GhcMod.Monad.Newtypes
|
||||||
|
|
||||||
#if DIFFERENT_MONADIO
|
#if DIFFERENT_MONADIO
|
||||||
import qualified MonadUtils as GHC (MonadIO(..))
|
import qualified MonadUtils as GHC (MonadIO(..))
|
@ -17,10 +17,10 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
||||||
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-}
|
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Monad.Out where
|
module GhcMod.Monad.Out where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Newtypes
|
import GhcMod.Monad.Newtypes
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.State.Strict (StateT(..))
|
import Control.Monad.State.Strict (StateT(..))
|
@ -17,10 +17,10 @@
|
|||||||
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving #-}
|
||||||
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
|
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Monad.State where
|
module GhcMod.Monad.State where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Newtypes
|
import GhcMod.Monad.Newtypes
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.State.Strict (StateT(..))
|
import Control.Monad.State.Strict (StateT(..))
|
@ -20,7 +20,7 @@
|
|||||||
{-# LANGUAGE StandaloneDeriving #-}
|
{-# LANGUAGE StandaloneDeriving #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Monad.Types (
|
module GhcMod.Monad.Types (
|
||||||
-- * Monad Types
|
-- * Monad Types
|
||||||
GhcModT
|
GhcModT
|
||||||
, GmOutT(..)
|
, GmOutT(..)
|
||||||
@ -64,14 +64,14 @@ module Language.Haskell.GhcMod.Monad.Types (
|
|||||||
|
|
||||||
#include "Compat.hs_h"
|
#include "Compat.hs_h"
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Monad.Env
|
import GhcMod.Monad.Env
|
||||||
import Language.Haskell.GhcMod.Monad.State
|
import GhcMod.Monad.State
|
||||||
import Language.Haskell.GhcMod.Monad.Log
|
import GhcMod.Monad.Log
|
||||||
import Language.Haskell.GhcMod.Monad.Out
|
import GhcMod.Monad.Out
|
||||||
import Language.Haskell.GhcMod.Monad.Newtypes
|
import GhcMod.Monad.Newtypes
|
||||||
import Language.Haskell.GhcMod.Monad.Orphans ()
|
import GhcMod.Monad.Orphans ()
|
||||||
|
|
||||||
import Safe
|
import Safe
|
||||||
|
|
@ -14,7 +14,7 @@
|
|||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Options.DocUtils (
|
module GhcMod.Options.DocUtils (
|
||||||
($$),
|
($$),
|
||||||
($$$),
|
($$$),
|
||||||
(<=>),
|
(<=>),
|
@ -15,7 +15,7 @@
|
|||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
{-# LANGUAGE OverloadedStrings, FlexibleInstances, GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE OverloadedStrings, FlexibleInstances, GeneralizedNewtypeDeriving #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Options.Help where
|
module GhcMod.Options.Help where
|
||||||
|
|
||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
import Options.Applicative.Help.Pretty (Doc)
|
import Options.Applicative.Help.Pretty (Doc)
|
@ -16,20 +16,20 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Options.Options (
|
module GhcMod.Options.Options (
|
||||||
globalArgSpec
|
globalArgSpec
|
||||||
, parseCmdLineOptions
|
, parseCmdLineOptions
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
import Options.Applicative.Types
|
import Options.Applicative.Types
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
import Data.Char (toUpper, toLower)
|
import Data.Char (toUpper, toLower)
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate)
|
||||||
import Language.Haskell.GhcMod.Read
|
import GhcMod.Read
|
||||||
import Language.Haskell.GhcMod.Options.DocUtils
|
import GhcMod.Options.DocUtils
|
||||||
import Language.Haskell.GhcMod.Options.Help
|
import GhcMod.Options.Help
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
@ -18,7 +18,7 @@
|
|||||||
-- Copyright (c) The University of Glasgow 2004-2008
|
-- Copyright (c) The University of Glasgow 2004-2008
|
||||||
|
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
module Language.Haskell.GhcMod.Output (
|
module GhcMod.Output (
|
||||||
gmPutStr
|
gmPutStr
|
||||||
, gmErrStr
|
, gmErrStr
|
||||||
, gmPutStrLn
|
, gmPutStrLn
|
||||||
@ -53,9 +53,9 @@ import Pipes
|
|||||||
import Pipes.Lift
|
import Pipes.Lift
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types hiding (LineSeparator, MonadIO(..))
|
import GhcMod.Types hiding (LineSeparator, MonadIO(..))
|
||||||
import Language.Haskell.GhcMod.Monad.Types hiding (MonadIO(..))
|
import GhcMod.Monad.Types hiding (MonadIO(..))
|
||||||
import Language.Haskell.GhcMod.Gap ()
|
import GhcMod.Gap ()
|
||||||
|
|
||||||
class ProcessOutput a where
|
class ProcessOutput a where
|
||||||
hGetContents' :: Handle -> IO a
|
hGetContents' :: Handle -> IO a
|
@ -14,9 +14,9 @@
|
|||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.PathsAndFiles (
|
module GhcMod.PathsAndFiles (
|
||||||
module Language.Haskell.GhcMod.PathsAndFiles
|
module GhcMod.PathsAndFiles
|
||||||
, module Language.Haskell.GhcMod.Caching
|
, module GhcMod.Caching
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Config (cProjectVersion)
|
import Config (cProjectVersion)
|
||||||
@ -34,9 +34,9 @@ import System.Directory
|
|||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Process
|
import System.Process
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Caching
|
import GhcMod.Caching
|
||||||
import qualified Language.Haskell.GhcMod.Utils as U
|
import qualified GhcMod.Utils as U
|
||||||
import Utils (mightExist)
|
import Utils (mightExist)
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
@ -14,7 +14,7 @@
|
|||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Pretty
|
module GhcMod.Pretty
|
||||||
( renderGm
|
( renderGm
|
||||||
, renderSDoc
|
, renderSDoc
|
||||||
, gmComponentNameDoc
|
, gmComponentNameDoc
|
||||||
@ -35,9 +35,9 @@ import Pretty
|
|||||||
import GHC
|
import GHC
|
||||||
import Outputable (SDoc, withPprStyleDoc)
|
import Outputable (SDoc, withPprStyleDoc)
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Doc
|
import GhcMod.Doc
|
||||||
import Language.Haskell.GhcMod.Gap (renderGm)
|
import GhcMod.Gap (renderGm)
|
||||||
|
|
||||||
renderSDoc :: GhcMonad m => SDoc -> m Doc
|
renderSDoc :: GhcMonad m => SDoc -> m Doc
|
||||||
renderSDoc sdoc = do
|
renderSDoc sdoc = do
|
@ -1,4 +1,4 @@
|
|||||||
module Language.Haskell.GhcMod.Read where
|
module GhcMod.Read where
|
||||||
|
|
||||||
import Text.Read (readPrec_to_S, readPrec, minPrec)
|
import Text.Read (readPrec_to_S, readPrec, minPrec)
|
||||||
import qualified Text.ParserCombinators.ReadP as P
|
import qualified Text.ParserCombinators.ReadP as P
|
@ -2,7 +2,7 @@
|
|||||||
{-# LANGUAGE CPP, TupleSections, FlexibleInstances, Rank2Types #-}
|
{-# LANGUAGE CPP, TupleSections, FlexibleInstances, Rank2Types #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.SrcUtils where
|
module GhcMod.SrcUtils where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import CoreUtils (exprType)
|
import CoreUtils (exprType)
|
||||||
@ -17,9 +17,9 @@ import qualified Type as G
|
|||||||
import GHC.SYB.Utils
|
import GHC.SYB.Utils
|
||||||
import GhcMonad
|
import GhcMonad
|
||||||
import qualified Language.Haskell.Exts as HE
|
import qualified Language.Haskell.Exts as HE
|
||||||
import Language.Haskell.GhcMod.Doc
|
import GhcMod.Doc
|
||||||
import Language.Haskell.GhcMod.Gap
|
import GhcMod.Gap
|
||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified GhcMod.Gap as Gap
|
||||||
import OccName (OccName)
|
import OccName (OccName)
|
||||||
import Outputable (PprStyle)
|
import Outputable (PprStyle)
|
||||||
import TcHsSyn (hsPatType)
|
import TcHsSyn (hsPatType)
|
@ -14,7 +14,7 @@
|
|||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Stack where
|
module GhcMod.Stack where
|
||||||
|
|
||||||
import Safe
|
import Safe
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
@ -30,12 +30,12 @@ import System.FilePath
|
|||||||
import System.Info.Extra
|
import System.Info.Extra
|
||||||
import Exception
|
import Exception
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import qualified Language.Haskell.GhcMod.Utils as U
|
import qualified GhcMod.Utils as U
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
patchStackPrograms :: (IOish m, GmOut m) => Cradle -> Programs -> m Programs
|
patchStackPrograms :: (IOish m, GmOut m) => Cradle -> Programs -> m Programs
|
@ -15,7 +15,7 @@
|
|||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
{-# LANGUAGE CPP, ViewPatterns, NamedFieldPuns, RankNTypes #-}
|
{-# LANGUAGE CPP, ViewPatterns, NamedFieldPuns, RankNTypes #-}
|
||||||
module Language.Haskell.GhcMod.Target where
|
module GhcMod.Target where
|
||||||
|
|
||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
@ -30,20 +30,20 @@ import DynFlags
|
|||||||
import HscTypes
|
import HscTypes
|
||||||
import Pretty
|
import Pretty
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.DynFlags
|
import GhcMod.DynFlags
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.CabalHelper
|
import GhcMod.CabalHelper
|
||||||
import Language.Haskell.GhcMod.HomeModuleGraph
|
import GhcMod.HomeModuleGraph
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Language.Haskell.GhcMod.GhcPkg
|
import GhcMod.GhcPkg
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Utils as U
|
import GhcMod.Utils as U
|
||||||
import Language.Haskell.GhcMod.FileMapping
|
import GhcMod.FileMapping
|
||||||
import Language.Haskell.GhcMod.LightGhc
|
import GhcMod.LightGhc
|
||||||
import Language.Haskell.GhcMod.CustomPackageDb
|
import GhcMod.CustomPackageDb
|
||||||
import Language.Haskell.GhcMod.Output
|
import GhcMod.Output
|
||||||
|
|
||||||
import Safe
|
import Safe
|
||||||
import Data.Maybe
|
import Data.Maybe
|
@ -2,8 +2,8 @@
|
|||||||
StandaloneDeriving, DefaultSignatures, FlexibleInstances, TemplateHaskell,
|
StandaloneDeriving, DefaultSignatures, FlexibleInstances, TemplateHaskell,
|
||||||
GeneralizedNewtypeDeriving #-}
|
GeneralizedNewtypeDeriving #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-deprecations #-}
|
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-deprecations #-}
|
||||||
module Language.Haskell.GhcMod.Types (
|
module GhcMod.Types (
|
||||||
module Language.Haskell.GhcMod.Types
|
module GhcMod.Types
|
||||||
, ModuleName
|
, ModuleName
|
||||||
, mkModuleName
|
, mkModuleName
|
||||||
, moduleNameString
|
, moduleNameString
|
||||||
@ -40,7 +40,7 @@ import GHC.Generics
|
|||||||
import Pretty (Doc)
|
import Pretty (Doc)
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Caching.Types
|
import GhcMod.Caching.Types
|
||||||
|
|
||||||
-- | A constraint alias (-XConstraintKinds) to make functions dealing with
|
-- | A constraint alias (-XConstraintKinds) to make functions dealing with
|
||||||
-- 'GhcModT' somewhat cleaner.
|
-- 'GhcModT' somewhat cleaner.
|
@ -17,8 +17,8 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DoAndIfThenElse #-}
|
{-# LANGUAGE DoAndIfThenElse #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Utils (
|
module GhcMod.Utils (
|
||||||
module Language.Haskell.GhcMod.Utils
|
module GhcMod.Utils
|
||||||
, module Utils
|
, module Utils
|
||||||
, readProcess
|
, readProcess
|
||||||
) where
|
) where
|
||||||
@ -30,9 +30,9 @@ import Data.Maybe (fromMaybe)
|
|||||||
import Data.Either (rights)
|
import Data.Either (rights)
|
||||||
import Data.List (inits)
|
import Data.List (inits)
|
||||||
import Exception
|
import Exception
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.Environment
|
import System.Environment
|
||||||
import System.FilePath
|
import System.FilePath
|
@ -1,10 +1,10 @@
|
|||||||
module Language.Haskell.GhcMod.World where
|
module GhcMod.World where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.GhcPkg
|
import GhcMod.GhcPkg
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad.Types
|
import GhcMod.Monad.Types
|
||||||
import Language.Haskell.GhcMod.Utils
|
import GhcMod.Utils
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.Maybe
|
import Data.Maybe
|
122
ghc-mod.cabal
122
ghc-mod.cabal
@ -30,7 +30,7 @@ Data-Files: elisp/Makefile
|
|||||||
elisp/*.el
|
elisp/*.el
|
||||||
Extra-Source-Files: ChangeLog
|
Extra-Source-Files: ChangeLog
|
||||||
README.md
|
README.md
|
||||||
core/Language/Haskell/GhcMod/Monad/Compat.hs_h
|
core/GhcMod/Monad/Compat.hs_h
|
||||||
test/data/annotations/*.hs
|
test/data/annotations/*.hs
|
||||||
test/data/broken-cabal/*.cabal
|
test/data/broken-cabal/*.cabal
|
||||||
test/data/broken-sandbox/cabal.sandbox.config
|
test/data/broken-sandbox/cabal.sandbox.config
|
||||||
@ -110,60 +110,60 @@ Library
|
|||||||
HS-Source-Dirs: ., core, shared
|
HS-Source-Dirs: ., core, shared
|
||||||
Exposed-Modules:
|
Exposed-Modules:
|
||||||
GhcMod
|
GhcMod
|
||||||
GhcModExe.Boot
|
GhcMod.Exe.Boot
|
||||||
GhcModExe.Browse
|
GhcMod.Exe.Browse
|
||||||
GhcModExe.CaseSplit
|
GhcMod.Exe.CaseSplit
|
||||||
GhcModExe.Check
|
GhcMod.Exe.Check
|
||||||
GhcModExe.Debug
|
GhcMod.Exe.Debug
|
||||||
GhcModExe.FillSig
|
GhcMod.Exe.FillSig
|
||||||
GhcModExe.Find
|
GhcMod.Exe.Find
|
||||||
GhcModExe.Flag
|
GhcMod.Exe.Flag
|
||||||
GhcModExe.Info
|
GhcMod.Exe.Info
|
||||||
GhcModExe.Internal
|
GhcMod.Exe.Internal
|
||||||
GhcModExe.Lang
|
GhcMod.Exe.Lang
|
||||||
GhcModExe.Lint
|
GhcMod.Exe.Lint
|
||||||
GhcModExe.Modules
|
GhcMod.Exe.Modules
|
||||||
GhcModExe.PkgDoc
|
GhcMod.Exe.PkgDoc
|
||||||
GhcModExe.Test
|
GhcMod.Exe.Test
|
||||||
Language.Haskell.GhcMod.CabalHelper
|
GhcMod.CabalHelper
|
||||||
Language.Haskell.GhcMod.Caching
|
GhcMod.Caching
|
||||||
Language.Haskell.GhcMod.Caching.Types
|
GhcMod.Caching.Types
|
||||||
Language.Haskell.GhcMod.Convert
|
GhcMod.Convert
|
||||||
Language.Haskell.GhcMod.Cradle
|
GhcMod.Cradle
|
||||||
Language.Haskell.GhcMod.CustomPackageDb
|
GhcMod.CustomPackageDb
|
||||||
Language.Haskell.GhcMod.DebugLogger
|
GhcMod.DebugLogger
|
||||||
Language.Haskell.GhcMod.Doc
|
GhcMod.Doc
|
||||||
Language.Haskell.GhcMod.DynFlags
|
GhcMod.DynFlags
|
||||||
Language.Haskell.GhcMod.DynFlagsTH
|
GhcMod.DynFlagsTH
|
||||||
Language.Haskell.GhcMod.Error
|
GhcMod.Error
|
||||||
Language.Haskell.GhcMod.FileMapping
|
GhcMod.FileMapping
|
||||||
Language.Haskell.GhcMod.Gap
|
GhcMod.Gap
|
||||||
Language.Haskell.GhcMod.GhcPkg
|
GhcMod.GhcPkg
|
||||||
Language.Haskell.GhcMod.HomeModuleGraph
|
GhcMod.HomeModuleGraph
|
||||||
Language.Haskell.GhcMod.LightGhc
|
GhcMod.LightGhc
|
||||||
Language.Haskell.GhcMod.Logger
|
GhcMod.Logger
|
||||||
Language.Haskell.GhcMod.Logging
|
GhcMod.Logging
|
||||||
Language.Haskell.GhcMod.Monad
|
GhcMod.Monad
|
||||||
Language.Haskell.GhcMod.Monad.Env
|
GhcMod.Monad.Env
|
||||||
Language.Haskell.GhcMod.Monad.Log
|
GhcMod.Monad.Log
|
||||||
Language.Haskell.GhcMod.Monad.Newtypes
|
GhcMod.Monad.Newtypes
|
||||||
Language.Haskell.GhcMod.Monad.Orphans
|
GhcMod.Monad.Orphans
|
||||||
Language.Haskell.GhcMod.Monad.Out
|
GhcMod.Monad.Out
|
||||||
Language.Haskell.GhcMod.Monad.State
|
GhcMod.Monad.State
|
||||||
Language.Haskell.GhcMod.Monad.Types
|
GhcMod.Monad.Types
|
||||||
Language.Haskell.GhcMod.Options.DocUtils
|
GhcMod.Options.DocUtils
|
||||||
Language.Haskell.GhcMod.Options.Help
|
GhcMod.Options.Help
|
||||||
Language.Haskell.GhcMod.Options.Options
|
GhcMod.Options.Options
|
||||||
Language.Haskell.GhcMod.Output
|
GhcMod.Output
|
||||||
Language.Haskell.GhcMod.PathsAndFiles
|
GhcMod.PathsAndFiles
|
||||||
Language.Haskell.GhcMod.Pretty
|
GhcMod.Pretty
|
||||||
Language.Haskell.GhcMod.Read
|
GhcMod.Read
|
||||||
Language.Haskell.GhcMod.SrcUtils
|
GhcMod.SrcUtils
|
||||||
Language.Haskell.GhcMod.Stack
|
GhcMod.Stack
|
||||||
Language.Haskell.GhcMod.Target
|
GhcMod.Target
|
||||||
Language.Haskell.GhcMod.Types
|
GhcMod.Types
|
||||||
Language.Haskell.GhcMod.Utils
|
GhcMod.Utils
|
||||||
Language.Haskell.GhcMod.World
|
GhcMod.World
|
||||||
Other-Modules: Paths_ghc_mod
|
Other-Modules: Paths_ghc_mod
|
||||||
Utils
|
Utils
|
||||||
Data.Binary.Generic
|
Data.Binary.Generic
|
||||||
@ -213,12 +213,12 @@ Library
|
|||||||
|
|
||||||
Executable ghc-mod
|
Executable ghc-mod
|
||||||
Default-Language: Haskell2010
|
Default-Language: Haskell2010
|
||||||
Main-Is: GHCModMain.hs
|
Main-Is: GhcModMain.hs
|
||||||
Other-Modules: Paths_ghc_mod
|
Other-Modules: Paths_ghc_mod
|
||||||
, GHCMod.Options
|
, GhcMod.Exe.Options
|
||||||
, GHCMod.Options.Commands
|
, GhcMod.Exe.Options.Commands
|
||||||
, GHCMod.Version
|
, GhcMod.Exe.Version
|
||||||
, GHCMod.Options.ShellParse
|
, GhcMod.Exe.Options.ShellParse
|
||||||
GHC-Options: -Wall -fno-warn-deprecations -threaded
|
GHC-Options: -Wall -fno-warn-deprecations -threaded
|
||||||
Default-Extensions: ConstraintKinds, FlexibleContexts
|
Default-Extensions: ConstraintKinds, FlexibleContexts
|
||||||
HS-Source-Dirs: src, shared
|
HS-Source-Dirs: src, shared
|
||||||
@ -243,7 +243,7 @@ Executable ghc-mod
|
|||||||
|
|
||||||
Executable ghc-modi
|
Executable ghc-modi
|
||||||
Default-Language: Haskell2010
|
Default-Language: Haskell2010
|
||||||
Main-Is: GHCModi.hs
|
Main-Is: GhcModi.hs
|
||||||
Other-Modules: Paths_ghc_mod
|
Other-Modules: Paths_ghc_mod
|
||||||
Utils
|
Utils
|
||||||
System.Directory.ModTime
|
System.Directory.ModTime
|
||||||
|
@ -16,7 +16,7 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
||||||
|
|
||||||
module GHCMod.Options (
|
module GhcMod.Exe.Options (
|
||||||
parseArgs,
|
parseArgs,
|
||||||
parseArgsInteractive,
|
parseArgsInteractive,
|
||||||
GhcModCommands(..)
|
GhcModCommands(..)
|
||||||
@ -25,12 +25,12 @@ module GHCMod.Options (
|
|||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
import Options.Applicative.Types
|
import Options.Applicative.Types
|
||||||
|
|
||||||
import GHCMod.Options.Commands
|
import GhcMod.Exe.Options.Commands
|
||||||
import GHCMod.Options.ShellParse
|
import GhcMod.Exe.Options.ShellParse
|
||||||
import GHCMod.Version
|
import GhcMod.Exe.Version
|
||||||
import Language.Haskell.GhcMod.Options.DocUtils
|
import GhcMod.Options.DocUtils
|
||||||
import Language.Haskell.GhcMod.Options.Options
|
import GhcMod.Options.Options
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
|
|
||||||
parseArgs :: IO (Options, GhcModCommands)
|
parseArgs :: IO (Options, GhcModCommands)
|
||||||
parseArgs =
|
parseArgs =
|
@ -16,16 +16,16 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
{-# OPTIONS_GHC -fno-warn-unused-do-bind #-}
|
||||||
|
|
||||||
module GHCMod.Options.Commands where
|
module GhcMod.Exe.Options.Commands where
|
||||||
|
|
||||||
import Data.Semigroup
|
import Data.Semigroup
|
||||||
import Options.Applicative
|
import Options.Applicative
|
||||||
import Options.Applicative.Types
|
import Options.Applicative.Types
|
||||||
import Options.Applicative.Builder.Internal
|
import Options.Applicative.Builder.Internal
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Read
|
import GhcMod.Read
|
||||||
import Language.Haskell.GhcMod.Options.DocUtils
|
import GhcMod.Options.DocUtils
|
||||||
import Language.Haskell.GhcMod.Options.Help
|
import GhcMod.Options.Help
|
||||||
|
|
||||||
type Symbol = String
|
type Symbol = String
|
||||||
type Expr = String
|
type Expr = String
|
@ -13,7 +13,7 @@
|
|||||||
--
|
--
|
||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
module GHCMod.Options.ShellParse (parseCmdLine) where
|
module GhcMod.Exe.Options.ShellParse (parseCmdLine) where
|
||||||
|
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import Data.List
|
import Data.List
|
@ -14,7 +14,7 @@
|
|||||||
-- You should have received a copy of the GNU Affero General Public License
|
-- You should have received a copy of the GNU Affero General Public License
|
||||||
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
|
|
||||||
module GHCMod.Version where
|
module GhcMod.Exe.Version where
|
||||||
|
|
||||||
import Paths_ghc_mod
|
import Paths_ghc_mod
|
||||||
import Data.Version (showVersion)
|
import Data.Version (showVersion)
|
@ -7,7 +7,7 @@ import Control.Monad
|
|||||||
import Data.Typeable (Typeable)
|
import Data.Typeable (Typeable)
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.List.Split
|
import Data.List.Split
|
||||||
import Language.Haskell.GhcMod.Pretty
|
import GhcMod.Pretty
|
||||||
import System.FilePath ((</>))
|
import System.FilePath ((</>))
|
||||||
import System.Directory (setCurrentDirectory, getAppUserDataDirectory,
|
import System.Directory (setCurrentDirectory, getAppUserDataDirectory,
|
||||||
removeDirectoryRecursive)
|
removeDirectoryRecursive)
|
||||||
@ -15,12 +15,12 @@ import System.IO
|
|||||||
import System.Exit
|
import System.Exit
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import GHCMod.Options
|
|
||||||
import GhcMod
|
import GhcMod
|
||||||
import GhcModExe.Find
|
import GhcMod.Exe.Find
|
||||||
import GhcModExe.Internal hiding (MonadIO,liftIO)
|
import GhcMod.Exe.Options
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Exe.Internal hiding (MonadIO,liftIO)
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Monad
|
||||||
|
import GhcMod.Types
|
||||||
|
|
||||||
import Exception
|
import Exception
|
||||||
|
|
@ -4,9 +4,9 @@ module CabalHelperSpec where
|
|||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Distribution.Helper
|
import Distribution.Helper
|
||||||
import Language.Haskell.GhcMod.CabalHelper
|
import GhcMod.CabalHelper
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
@ -2,8 +2,8 @@ module CradleSpec where
|
|||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.List (isSuffixOf)
|
import Data.List (isSuffixOf)
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
import System.Directory (canonicalizePath)
|
import System.Directory (canonicalizePath)
|
||||||
import System.FilePath (pathSeparator)
|
import System.FilePath (pathSeparator)
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
@ -1,8 +1,8 @@
|
|||||||
module CustomPackageDbSpec where
|
module CustomPackageDbSpec where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.CabalHelper
|
import GhcMod.CabalHelper
|
||||||
import Language.Haskell.GhcMod.CustomPackageDb
|
import GhcMod.CustomPackageDb
|
||||||
import Language.Haskell.GhcMod.Error
|
import GhcMod.Error
|
||||||
import System.Process
|
import System.Process
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import Prelude
|
import Prelude
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
module FileMappingSpec where
|
module FileMappingSpec where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.FileMapping
|
import GhcMod.FileMapping
|
||||||
import Language.Haskell.GhcMod.Utils (withMappedFile)
|
import GhcMod.Utils (withMappedFile)
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import TestUtils
|
import TestUtils
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
module FindSpec where
|
module FindSpec where
|
||||||
|
|
||||||
import GhcModExe.Find
|
import GhcMod.Exe.Find
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import TestUtils
|
import TestUtils
|
||||||
|
|
||||||
|
@ -1,8 +1,8 @@
|
|||||||
module GhcPkgSpec where
|
module GhcPkgSpec where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.GhcPkg
|
import GhcMod.GhcPkg
|
||||||
import Language.Haskell.GhcMod.CabalHelper
|
import GhcMod.CabalHelper
|
||||||
import Language.Haskell.GhcMod.CustomPackageDb
|
import GhcMod.CustomPackageDb
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import System.Process (system)
|
import System.Process (system)
|
||||||
|
|
||||||
|
@ -18,8 +18,8 @@
|
|||||||
|
|
||||||
module HomeModuleGraphSpec where
|
module HomeModuleGraphSpec where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.HomeModuleGraph
|
import GhcMod.HomeModuleGraph
|
||||||
import Language.Haskell.GhcMod.LightGhc
|
import GhcMod.LightGhc
|
||||||
import TestUtils
|
import TestUtils
|
||||||
|
|
||||||
import GHC
|
import GHC
|
||||||
|
@ -1,9 +1,9 @@
|
|||||||
module PathsAndFilesSpec where
|
module PathsAndFilesSpec where
|
||||||
|
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.PathsAndFiles
|
import GhcMod.PathsAndFiles
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import GhcMod.Cradle
|
||||||
import qualified Language.Haskell.GhcMod.Utils as U
|
import qualified GhcMod.Utils as U
|
||||||
|
|
||||||
import Control.Monad.Trans.Maybe
|
import Control.Monad.Trans.Maybe
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
module ShellParseSpec where
|
module ShellParseSpec where
|
||||||
|
|
||||||
|
|
||||||
import GHCMod.Options.ShellParse
|
import GhcMod.Exe.Options.ShellParse
|
||||||
|
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
||||||
|
@ -1,9 +1,9 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
module TargetSpec where
|
module TargetSpec where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Target
|
import GhcMod.Target
|
||||||
import Language.Haskell.GhcMod.LightGhc
|
import GhcMod.LightGhc
|
||||||
import Language.Haskell.GhcMod.Gap
|
import GhcMod.Gap
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
|
|
||||||
import TestUtils
|
import TestUtils
|
||||||
|
@ -10,14 +10,14 @@ module TestUtils (
|
|||||||
, shouldReturnError
|
, shouldReturnError
|
||||||
, isPkgDbAt
|
, isPkgDbAt
|
||||||
, isPkgConfDAt
|
, isPkgConfDAt
|
||||||
, module Language.Haskell.GhcMod.Monad
|
, module GhcMod.Monad
|
||||||
, module Language.Haskell.GhcMod.Types
|
, module GhcMod.Types
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Logging
|
import GhcMod.Logging
|
||||||
import Language.Haskell.GhcMod.Monad
|
import GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Cradle
|
import GhcMod.Cradle
|
||||||
import Language.Haskell.GhcMod.Types
|
import GhcMod.Types
|
||||||
|
|
||||||
import Control.Arrow
|
import Control.Arrow
|
||||||
import Control.Category
|
import Control.Category
|
||||||
|
Loading…
Reference in New Issue
Block a user