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