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