Prepare for splitting off ghc-mod-core eventually

This commit is contained in:
Daniel Gröber 2017-01-12 16:36:47 +01:00
parent 8a8ffa18ec
commit ee55da4908
71 changed files with 99 additions and 92 deletions

View File

@ -1,6 +1,6 @@
-- | The ghc-mod library.
module Language.Haskell.GhcMod (
module GhcMod (
-- * Cradle
Cradle(..)
, Project(..)
@ -69,24 +69,24 @@ module Language.Haskell.GhcMod (
, unloadMappedFile
) where
import Language.Haskell.GhcMod.Boot
import Language.Haskell.GhcMod.Browse
import Language.Haskell.GhcMod.CaseSplit
import Language.Haskell.GhcMod.Check
import GhcMod.Boot
import GhcMod.Browse
import GhcMod.CaseSplit
import GhcMod.Check
import GhcMod.Debug
import GhcMod.FillSig
import GhcMod.Find
import GhcMod.Flag
import GhcMod.Info
import GhcMod.Lang
import GhcMod.Lint
import GhcMod.Modules
import GhcMod.PkgDoc
import GhcMod.Test
import Language.Haskell.GhcMod.Cradle
import Language.Haskell.GhcMod.Debug
import Language.Haskell.GhcMod.FillSig
import Language.Haskell.GhcMod.Find
import Language.Haskell.GhcMod.Flag
import Language.Haskell.GhcMod.Info
import Language.Haskell.GhcMod.Lang
import Language.Haskell.GhcMod.Lint
import Language.Haskell.GhcMod.Logging
import Language.Haskell.GhcMod.Modules
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.PkgDoc
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Target
import Language.Haskell.GhcMod.Output
import Language.Haskell.GhcMod.FileMapping
import Language.Haskell.GhcMod.Test
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

View File

@ -1,12 +1,13 @@
module Language.Haskell.GhcMod.Boot where
module GhcMod.Boot where
import Control.Applicative
import Prelude
import Language.Haskell.GhcMod.Browse
import Language.Haskell.GhcMod.Flag
import Language.Haskell.GhcMod.Lang
import GhcMod.Browse
import GhcMod.Flag
import GhcMod.Lang
import GhcMod.Modules
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Modules
import Language.Haskell.GhcMod.Types (defaultBrowseOpts)
-- | Printing necessary information for front-end booting.

View File

@ -1,5 +1,5 @@
{-# LANGUAGE CPP #-}
module Language.Haskell.GhcMod.Browse (
module GhcMod.Browse (
browse,
BrowseOpts(..)
) where

View File

@ -1,6 +1,6 @@
{-# LANGUAGE CPP #-}
module Language.Haskell.GhcMod.CaseSplit (
module GhcMod.CaseSplit (
splits
) where

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Check (
module GhcMod.Check (
checkSyntax
, check
, expandTemplate

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Debug (debugInfo, rootInfo, componentInfo) where
module GhcMod.Debug (debugInfo, rootInfo, componentInfo) where
import Control.Arrow (first)
import Control.Applicative
@ -9,20 +9,21 @@ import Data.Char
import Data.Version
import Data.List.Split
import System.Directory
import Pretty
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Internal
import Language.Haskell.GhcMod.Target
import Language.Haskell.GhcMod.Pretty
import Language.Haskell.GhcMod.Utils
import GhcMod.Internal
import Language.Haskell.GhcMod.Cradle
import Language.Haskell.GhcMod.Stack
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 Paths_ghc_mod (version)
import Config (cProjectVersion)
import Pretty
----------------------------------------------------------------

View File

@ -1,7 +1,7 @@
{-# LANGUAGE CPP, MultiParamTypeClasses, FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
module Language.Haskell.GhcMod.FillSig (
module GhcMod.FillSig (
sig
, refine
, auto

View File

@ -1,6 +1,6 @@
{-# LANGUAGE CPP, BangPatterns, TupleSections, DeriveGeneric #-}
module Language.Haskell.GhcMod.Find
module GhcMod.Find
#ifndef SPEC
( Symbol
, SymbolDb

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Flag where
module GhcMod.Flag where
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Convert

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Info (
module GhcMod.Info (
info
, types
) where
@ -10,8 +10,8 @@ import Exception (ghandle, SomeException(..))
import GHC (GhcMonad, SrcSpan)
import Prelude
import qualified GHC as G
import qualified Language.Haskell.GhcMod.Gap as Gap
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Doc
import Language.Haskell.GhcMod.DynFlags

View File

@ -1,6 +1,6 @@
-- | Low level access to the ghc-mod library.
module Language.Haskell.GhcMod.Internal (
module GhcMod.Internal (
-- * Types
GHCOption
, IncludeDir

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Lang where
module GhcMod.Lang where
import DynFlags (supportedLanguagesAndExtensions)
import Language.Haskell.GhcMod.Convert

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Lint where
module GhcMod.Lint where
import Exception (ghandle)
import Control.Exception (SomeException(..))

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Modules (modules) where
module GhcMod.Modules (modules) where
import Control.Arrow
import Data.List

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.PkgDoc (pkgDoc) where
module GhcMod.PkgDoc (pkgDoc) where
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.GhcPkg

View File

@ -1,4 +1,4 @@
module Language.Haskell.GhcMod.Test where
module GhcMod.Test where
import Control.Applicative
import Data.List

View File

@ -34,7 +34,7 @@ Extra-Source-Files: ChangeLog
SetupCompat.hs
NotCPP/*.hs
NotCPP/COPYING
Language/Haskell/GhcMod/Monad/Compat.hs_h
core/Language/Haskell/GhcMod/Monad/Compat.hs_h
test/data/annotations/*.hs
test/data/broken-cabal/*.cabal
test/data/broken-cabal/cabal.sandbox.config.in
@ -112,38 +112,42 @@ Library
Default-Extensions: ScopedTypeVariables, RecordWildCards, NamedFieldPuns,
ConstraintKinds, FlexibleContexts,
DataKinds, KindSignatures, TypeOperators, ViewPatterns
Exposed-Modules: Language.Haskell.GhcMod
Language.Haskell.GhcMod.Internal
Language.Haskell.GhcMod.Boot
Language.Haskell.GhcMod.Browse
HS-Source-Dirs: ., core
Exposed-Modules:
GhcMod
GhcMod.Boot
GhcMod.Browse
GhcMod.CaseSplit
GhcMod.Check
GhcMod.Debug
GhcMod.FillSig
GhcMod.Find
GhcMod.Flag
GhcMod.Info
GhcMod.Internal
GhcMod.Lang
GhcMod.Lint
GhcMod.Modules
GhcMod.PkgDoc
GhcMod.Test
Language.Haskell.GhcMod.CabalHelper
Language.Haskell.GhcMod.Caching
Language.Haskell.GhcMod.Caching.Types
Language.Haskell.GhcMod.CaseSplit
Language.Haskell.GhcMod.Check
Language.Haskell.GhcMod.Convert
Language.Haskell.GhcMod.Cradle
Language.Haskell.GhcMod.CustomPackageDb
Language.Haskell.GhcMod.Debug
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.FillSig
Language.Haskell.GhcMod.Find
Language.Haskell.GhcMod.Flag
Language.Haskell.GhcMod.Gap
Language.Haskell.GhcMod.GhcPkg
Language.Haskell.GhcMod.HomeModuleGraph
Language.Haskell.GhcMod.Info
Language.Haskell.GhcMod.Lang
Language.Haskell.GhcMod.Lint
Language.Haskell.GhcMod.LightGhc
Language.Haskell.GhcMod.Logger
Language.Haskell.GhcMod.Logging
Language.Haskell.GhcMod.Modules
Language.Haskell.GhcMod.Monad
Language.Haskell.GhcMod.Monad.Env
Language.Haskell.GhcMod.Monad.Log
@ -152,21 +156,19 @@ Library
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.PkgDoc
Language.Haskell.GhcMod.Pretty
Language.Haskell.GhcMod.Read
Language.Haskell.GhcMod.SrcUtils
Language.Haskell.GhcMod.Stack
Language.Haskell.GhcMod.Target
Language.Haskell.GhcMod.Test
Language.Haskell.GhcMod.Types
Language.Haskell.GhcMod.Utils
Language.Haskell.GhcMod.World
Language.Haskell.GhcMod.Options.Options
Language.Haskell.GhcMod.Options.DocUtils
Language.Haskell.GhcMod.Options.Help
Other-Modules: Paths_ghc_mod
Utils
Data.Binary.Generic

View File

@ -7,21 +7,23 @@ import Control.Monad
import Data.Typeable (Typeable)
import Data.List
import Data.List.Split
import Exception
import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Internal hiding (MonadIO,liftIO)
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Find
import Language.Haskell.GhcMod.Pretty
import System.FilePath ((</>))
import System.Directory (setCurrentDirectory, getAppUserDataDirectory,
removeDirectoryRecursive)
import System.IO
import System.Exit
import GHCMod.Options
import Prelude
import GHCMod.Options
import GhcMod
import GhcMod.Find
import GhcMod.Internal hiding (MonadIO,liftIO)
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Types
import Exception
handler :: IOish m => GhcModT m a -> GhcModT m a
handler = flip gcatches
[ GHandler $ \(e :: ExitCode) -> throw e

View File

@ -24,12 +24,13 @@ module GHCMod.Options (
import Options.Applicative
import Options.Applicative.Types
import Language.Haskell.GhcMod.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 GHCMod.Options.ShellParse
import Language.Haskell.GhcMod.Types
parseArgs :: IO (Options, GhcModCommands)
parseArgs =
@ -69,4 +70,3 @@ helpVersion =
argAndCmdSpec :: Parser (Options, GhcModCommands)
argAndCmdSpec = (,) <$> globalArgSpec <*> commandsSpec

View File

@ -1,7 +1,7 @@
module BrowseSpec where
import Control.Applicative
import Language.Haskell.GhcMod
import GhcMod
import Test.Hspec
import Prelude

View File

@ -1,7 +1,7 @@
{-# LANGUAGE CPP #-}
module CaseSplitSpec where
import Language.Haskell.GhcMod
import GhcMod
import Test.Hspec
import TestUtils
import Dir

View File

@ -1,7 +1,7 @@
{-# LANGUAGE CPP #-}
module CheckSpec where
import Language.Haskell.GhcMod
import GhcMod
import Data.List
import System.Process

View File

@ -9,7 +9,7 @@ import Dir
import System.IO.Temp
import System.Directory
import Language.Haskell.GhcMod
import GhcMod
spec :: Spec
spec = do

View File

@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module FindSpec where
import Language.Haskell.GhcMod.Find
import GhcMod.Find
import Test.Hspec
import TestUtils

View File

@ -1,7 +1,7 @@
module FlagSpec where
import Control.Applicative
import Language.Haskell.GhcMod
import GhcMod
import Test.Hspec
import TestUtils
import Prelude

View File

@ -3,7 +3,7 @@ module InfoSpec where
import Control.Applicative
import Data.List (isPrefixOf)
import Language.Haskell.GhcMod
import GhcMod
#if __GLASGOW_HASKELL__ < 706
import System.Environment.Executable (getExecutablePath)
#else

View File

@ -1,7 +1,7 @@
module LangSpec where
import Control.Applicative
import Language.Haskell.GhcMod
import GhcMod
import Test.Hspec
import TestUtils
import Prelude

View File

@ -1,6 +1,6 @@
module LintSpec where
import Language.Haskell.GhcMod
import GhcMod
import Test.Hspec
import TestUtils

View File

@ -1,7 +1,7 @@
module ListSpec where
import Control.Applicative
import Language.Haskell.GhcMod
import GhcMod
import Test.Hspec
import TestUtils
import Prelude

View File

@ -4,7 +4,7 @@ import Dir
import Control.Exception as E
import Control.Monad (void)
import Language.Haskell.GhcMod (debugInfo)
import GhcMod (debugInfo)
import System.Process
import System.Environment
import Test.Hspec

View File

@ -15,7 +15,8 @@ main = do
, "-package", "directory-" ++ VERSION_directory
, "-XScopedTypeVariables", "-XRecordWildCards", "-XNamedFieldPuns", "-XConstraintKinds", "-XFlexibleContexts", "-XDataKinds", "-XKindSignatures", "-XTypeOperators", "-XViewPatterns"
, "-i" ++ distdir ++ "/build/autogen/"
, "-optP-include"
, "-optP" ++ distdir ++ "/build/autogen/cabal_macros.h"
, "Language/Haskell/GhcMod.hs"
, "-icore/"
-- , "-optP-include"
-- , "-optP" ++ distdir ++ "/build/autogen/cabal_macros.h"
, "GhcMod.hs"
]