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:
@@ -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
|
||||
Reference in New Issue
Block a user