Changing GHCMod as a library.

This commit is contained in:
Kazu Yamamoto 2013-05-17 10:00:01 +09:00
parent 1977b8858a
commit bac4bbbcf3
20 changed files with 113 additions and 84 deletions

View File

@ -1,7 +0,0 @@
module Lang where
import qualified Gap
import Types
listLanguages :: Options -> IO String
listLanguages opt = return $ convert opt Gap.supportedExtensions

View File

@ -0,0 +1,27 @@
module Language.Haskell.GhcMod (
browseModule
, checkSyntax
, module Language.Haskell.GhcMod.Cradle
, debugInfo
, debug
, infoExpr
, typeExpr
, listLanguages
, lintSyntax
, listModules
, module Language.Haskell.GhcMod.Types
, listFlags
, getGHCVersion
) where
import Language.Haskell.GhcMod.Browse
import Language.Haskell.GhcMod.Check
import Language.Haskell.GhcMod.Cradle
import Language.Haskell.GhcMod.Debug
import Language.Haskell.GhcMod.Flag
import Language.Haskell.GhcMod.Info
import Language.Haskell.GhcMod.Lang
import Language.Haskell.GhcMod.Lint
import Language.Haskell.GhcMod.List
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.CabalApi

View File

@ -1,18 +1,18 @@
module Browse (browseModule) where
module Language.Haskell.GhcMod.Browse (browseModule) where
import Control.Applicative
import Data.Char
import Data.List
import Data.Maybe (fromMaybe)
import DataCon (dataConRepType)
import Doc
import GHC
import GHCApi
import Language.Haskell.GhcMod.Doc
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Types
import Name
import Outputable
import TyCon
import Type
import Types
import Var
----------------------------------------------------------------

View File

@ -1,6 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
module CabalApi (
module Language.Haskell.GhcMod.CabalApi (
fromCabalFile
, cabalParseFile
, cabalBuildInfo
@ -22,8 +22,8 @@ import Distribution.Simple.Program.Types (programName, programFindVersion)
import Distribution.Text (display)
import Distribution.Verbosity (silent)
import Distribution.Version (versionBranch)
import Language.Haskell.GhcMod.Types
import System.FilePath
import Types
----------------------------------------------------------------

View File

@ -1,14 +1,14 @@
module Check (checkSyntax) where
module Language.Haskell.GhcMod.Check (checkSyntax) where
import Control.Applicative
import Control.Monad
import CoreMonad
import ErrMsg
import Exception
import GHC
import GHCApi
import Language.Haskell.GhcMod.ErrMsg
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Types
import Prelude
import Types
----------------------------------------------------------------

View File

@ -1,12 +1,12 @@
module Cradle (findCradle) where
module Language.Haskell.GhcMod.Cradle (findCradle) where
import Control.Applicative ((<$>))
import Control.Exception (throwIO)
import Control.Monad
import Data.List (isSuffixOf)
import Language.Haskell.GhcMod.Types
import System.Directory
import System.FilePath ((</>),takeDirectory)
import Types
-- An error would be thrown
findCradle :: Maybe FilePath -> String -> IO Cradle

View File

@ -1,15 +1,15 @@
module Debug (debugInfo, debug) where
module Language.Haskell.GhcMod.Debug (debugInfo, debug) where
import CabalApi
import Control.Applicative
import Control.Exception.IOChoice
import Control.Monad
import Data.List (intercalate)
import Data.Maybe
import GHC
import GHCApi
import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Types
import Prelude
import Types
----------------------------------------------------------------

View File

@ -1,7 +1,7 @@
module Doc where
module Language.Haskell.GhcMod.Doc where
import DynFlags (DynFlags)
import Gap (withStyle)
import Language.Haskell.GhcMod.Gap (withStyle)
import Outputable
import Pretty

View File

@ -1,6 +1,6 @@
{-# LANGUAGE BangPatterns #-}
module ErrMsg (
module Language.Haskell.GhcMod.ErrMsg (
LogReader
, setLogger
, handleErrMsg
@ -10,12 +10,12 @@ import Bag
import Control.Applicative
import Data.IORef
import Data.Maybe
import Doc
import DynFlags
import ErrUtils
import GHC
import qualified Gap
import HscTypes
import Language.Haskell.GhcMod.Doc
import qualified Language.Haskell.GhcMod.Gap as Gap
import Outputable
import System.FilePath (normalise)

View File

@ -1,9 +1,9 @@
{-# LANGUAGE CPP #-}
module Flag where
module Language.Haskell.GhcMod.Flag where
import Types
import qualified Gap
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types
listFlags :: Options -> IO String
listFlags opt = return $ convert opt [ "-f" ++ prefix ++ option

View File

@ -1,6 +1,6 @@
{-# LANGUAGE ScopedTypeVariables #-}
module GHCApi (
module Language.Haskell.GhcMod.GHCApi (
withGHC
, withGHCDummyFile
, initializeFlags
@ -12,21 +12,21 @@ module GHCApi (
, canCheckFast
) where
import CabalApi
import Control.Applicative
import Control.Exception
import Control.Monad
import CoreMonad
import Data.Maybe (isJust)
import DynFlags
import ErrMsg
import Exception
import GHC
import GHCChoice
import GHC.Paths (libdir)
import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.ErrMsg
import Language.Haskell.GhcMod.GHCChoice
import Language.Haskell.GhcMod.Types
import System.Exit
import System.IO
import Types
----------------------------------------------------------------

View File

@ -1,6 +1,6 @@
{-# LANGUAGE ScopedTypeVariables #-}
module GHCChoice where
module Language.Haskell.GhcMod.GHCChoice where
import Control.Exception
import CoreMonad

View File

@ -1,7 +1,7 @@
{-# LANGUAGE CPP #-}
module Gap (
Gap.ClsInst
module Language.Haskell.GhcMod.Gap (
Language.Haskell.GhcMod.Gap.ClsInst
, mkTarget
, withStyle
, setLogAction
@ -26,7 +26,7 @@ import DynFlags
import ErrUtils
import FastString
import GHC
import GHCChoice
import Language.Haskell.GhcMod.GHCChoice
import Outputable
import StringBuffer

View File

@ -1,7 +1,7 @@
{-# LANGUAGE TupleSections, FlexibleInstances, TypeSynonymInstances #-}
{-# LANGUAGE Rank2Types #-}
module Info (infoExpr, typeExpr) where
module Language.Haskell.GhcMod.Info (infoExpr, typeExpr) where
import Control.Applicative
import Control.Monad (void, when)
@ -13,19 +13,19 @@ import Data.Maybe
import Data.Ord as O
import Data.Time.Clock
import Desugar
import Doc
import GHC
import GHC.SYB.Utils
import GHCApi
import GHCChoice
import qualified Gap
import HscTypes
import Language.Haskell.GhcMod.Doc
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.GHCChoice
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types
import NameSet
import Outputable
import PprTyThing
import TcHsSyn (hsPatType)
import TcRnTypes
import Types
----------------------------------------------------------------
@ -68,7 +68,7 @@ instance HasType (LPat Id) where
getType _ (L spn pat) = return $ Just (spn, hsPatType pat)
typeExpr :: Options -> Cradle -> ModuleString -> Int -> Int -> FilePath -> IO String
typeExpr opt cradle modstr lineNo colNo file = Info.typeOf opt cradle file modstr lineNo colNo
typeExpr opt cradle modstr lineNo colNo file = Language.Haskell.GhcMod.Info.typeOf opt cradle file modstr lineNo colNo
typeOf :: Options -> Cradle -> FilePath -> ModuleString -> Int -> Int -> IO String
typeOf opt cradle fileName modstr lineNo colNo =

View File

@ -0,0 +1,7 @@
module Language.Haskell.GhcMod.Lang where
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types
listLanguages :: Options -> IO String
listLanguages opt = return $ convert opt Gap.supportedExtensions

View File

@ -1,9 +1,9 @@
module Lint where
module Language.Haskell.GhcMod.Lint where
import Control.Applicative
import Data.List
import Language.Haskell.GhcMod.Types
import Language.Haskell.HLint
import Types
lintSyntax :: Options -> String -> IO String
lintSyntax opt file = pack <$> lint opt file

View File

@ -1,11 +1,11 @@
module List (listModules) where
module Language.Haskell.GhcMod.List (listModules) where
import Control.Applicative
import Data.List
import GHC
import GHCApi
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Types
import Packages
import Types
import UniqFM
----------------------------------------------------------------

View File

@ -1,6 +1,6 @@
{-# LANGUAGE FlexibleInstances #-}
module Types where
module Language.Haskell.GhcMod.Types where
data OutputStyle = LispStyle | PlainStyle

View File

@ -1,5 +1,5 @@
Name: ghc-mod
Version: 1.12.5
Version: 2.0.0
Author: Kazu Yamamoto <kazu@iij.ad.jp>
Maintainer: Kazu Yamamoto <kazu@iij.ad.jp>
License: BSD3
@ -37,27 +37,27 @@ Extra-Source-Files: ChangeLog
test/data/check-test-subdir/test/*.hs
test/data/check-test-subdir/test/Bar/*.hs
test/data/check-test-subdir/src/Check/Test/*.hs
Executable ghc-mod
Library
Default-Language: Haskell2010
Main-Is: GHCMod.hs
Other-Modules: Browse
CabalApi
Check
Cradle
Doc
Debug
ErrMsg
Flag
GHCApi
GHCChoice
Gap
Info
Lang
Lint
List
Paths_ghc_mod
Types
GHC-Options: -Wall
Exposed-Modules: Language.Haskell.GhcMod
Other-Modules: Language.Haskell.GhcMod.Browse
Language.Haskell.GhcMod.CabalApi
Language.Haskell.GhcMod.Check
Language.Haskell.GhcMod.Cradle
Language.Haskell.GhcMod.Doc
Language.Haskell.GhcMod.Debug
Language.Haskell.GhcMod.ErrMsg
Language.Haskell.GhcMod.Flag
Language.Haskell.GhcMod.GHCApi
Language.Haskell.GhcMod.GHCChoice
Language.Haskell.GhcMod.Gap
Language.Haskell.GhcMod.Info
Language.Haskell.GhcMod.Lang
Language.Haskell.GhcMod.Lint
Language.Haskell.GhcMod.List
Language.Haskell.GhcMod.Types
Build-Depends: base >= 4.0 && < 5
, Cabal >= 1.10
, containers
@ -75,6 +75,18 @@ Executable ghc-mod
, time
, transformers
Executable ghc-mod
Default-Language: Haskell2010
Main-Is: GHCMod.hs
Other-Modules: Paths_ghc_mod
GHC-Options: -Wall
HS-Source-Dirs: src
Build-Depends: base >= 4.0 && < 5
, directory
, filepath
, ghc
, ghc-mod
Test-Suite spec
Default-Language: Haskell2010
Main-Is: Spec.hs

View File

@ -2,27 +2,17 @@
module Main where
import Browse
import CabalApi
import Check
import Control.Applicative
import Control.Exception
import Cradle
import Data.Typeable
import Data.Version
import Debug
import Flag
import Info
import Lang
import Lint
import List
import Language.Haskell.GhcMod
import Paths_ghc_mod
import Prelude
import System.Console.GetOpt
import System.Directory
import System.Environment (getArgs)
import System.IO (hPutStr, hPutStrLn, stdout, stderr, hSetEncoding, utf8)
import Types
----------------------------------------------------------------