writing docs.
This commit is contained in:
parent
849c308e5c
commit
089d490607
@ -3,31 +3,35 @@ module Language.Haskell.GhcMod (
|
|||||||
Cradle(..)
|
Cradle(..)
|
||||||
, findCradle
|
, findCradle
|
||||||
-- * GHC version
|
-- * GHC version
|
||||||
|
, GHCVersion
|
||||||
, getGHCVersion
|
, getGHCVersion
|
||||||
-- * Options
|
-- * Options
|
||||||
, Options(..)
|
, Options(..)
|
||||||
, OutputStyle(..)
|
, OutputStyle(..)
|
||||||
, defaultOptions
|
, defaultOptions
|
||||||
|
-- * Types
|
||||||
|
, ModuleString
|
||||||
|
, Expression
|
||||||
-- * 'IO' utilities
|
-- * 'IO' utilities
|
||||||
, browseModule
|
, browseModule
|
||||||
, checkSyntax
|
, checkSyntax
|
||||||
, debugInfo
|
, lintSyntax
|
||||||
, infoExpr
|
, infoExpr
|
||||||
, typeExpr
|
, typeExpr
|
||||||
, listModules
|
, listModules
|
||||||
, listLanguages
|
, listLanguages
|
||||||
, listFlags
|
, listFlags
|
||||||
, lintSyntax
|
, debugInfo
|
||||||
-- * Converting the 'Ghc' monad to the 'IO' monad
|
-- * Converting the 'Ghc' monad to the 'IO' monad
|
||||||
, withGHC
|
, withGHC
|
||||||
, withGHCDummyFile
|
, withGHCDummyFile
|
||||||
-- * 'Ghc' utilities
|
-- * 'Ghc' utilities
|
||||||
, browse
|
, browse
|
||||||
, check
|
, check
|
||||||
, debug
|
|
||||||
, info
|
, info
|
||||||
, typeOf
|
, typeOf
|
||||||
, list
|
, listMods
|
||||||
|
, debug
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.Browse
|
import Language.Haskell.GhcMod.Browse
|
||||||
|
@ -17,7 +17,11 @@ import Var
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
browseModule :: Options -> String -> IO String
|
-- | Getting functions, classes, etc from a module.
|
||||||
|
-- If 'detailed' is 'True', their types are also obtained.
|
||||||
|
browseModule :: Options
|
||||||
|
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
||||||
|
-> IO String
|
||||||
browseModule opt mdlName = convert opt . format <$> withGHCDummyFile (browse opt mdlName)
|
browseModule opt mdlName = convert opt . format <$> withGHCDummyFile (browse opt mdlName)
|
||||||
where
|
where
|
||||||
format
|
format
|
||||||
@ -32,7 +36,11 @@ browseModule opt mdlName = convert opt . format <$> withGHCDummyFile (browse opt
|
|||||||
(name, tail_) = break isSpace x
|
(name, tail_) = break isSpace x
|
||||||
formatOps' [] = error "formatOps'"
|
formatOps' [] = error "formatOps'"
|
||||||
|
|
||||||
browse :: Options -> String -> Ghc [String]
|
-- | Getting functions, classes, etc from a module.
|
||||||
|
-- If 'detailed' is 'True', their types are also obtained.
|
||||||
|
browse :: Options
|
||||||
|
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
||||||
|
-> Ghc [String]
|
||||||
browse opt mdlName = do
|
browse opt mdlName = do
|
||||||
initializeFlags opt
|
initializeFlags opt
|
||||||
getModule >>= getModuleInfo >>= listExports
|
getModule >>= getModuleInfo >>= listExports
|
||||||
|
@ -129,7 +129,8 @@ uniqueAndSort = toList . fromList
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
getGHCVersion :: IO (String, Int)
|
-- | Getting GHC version. 7.6.3 becames 706 in the second of the result.
|
||||||
|
getGHCVersion :: IO (GHCVersion, Int)
|
||||||
getGHCVersion = ghcVer >>= toTupple
|
getGHCVersion = ghcVer >>= toTupple
|
||||||
where
|
where
|
||||||
ghcVer = programFindVersion ghcProgram silent (programName ghcProgram)
|
ghcVer = programFindVersion ghcProgram silent (programName ghcProgram)
|
||||||
|
@ -12,12 +12,22 @@ import Prelude
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
checkSyntax :: Options -> Cradle -> FilePath -> IO String
|
-- | Checking syntax of a target file using GHC.
|
||||||
|
-- Warnings and errors are returned.
|
||||||
|
checkSyntax :: Options
|
||||||
|
-> Cradle
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> IO String
|
||||||
checkSyntax opt cradle file = unlines <$> withGHC file (check opt cradle file)
|
checkSyntax opt cradle file = unlines <$> withGHC file (check opt cradle file)
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
check :: Options -> Cradle -> FilePath -> Ghc [String]
|
-- | Checking syntax of a target file using GHC.
|
||||||
|
-- Warnings and errors are returned.
|
||||||
|
check :: Options
|
||||||
|
-> Cradle
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> Ghc [String]
|
||||||
check opt cradle fileName = checkIt `gcatch` handleErrMsg
|
check opt cradle fileName = checkIt `gcatch` handleErrMsg
|
||||||
where
|
where
|
||||||
checkIt = do
|
checkIt = do
|
||||||
|
@ -8,8 +8,11 @@ import Language.Haskell.GhcMod.Types
|
|||||||
import System.Directory
|
import System.Directory
|
||||||
import System.FilePath ((</>),takeDirectory)
|
import System.FilePath ((</>),takeDirectory)
|
||||||
|
|
||||||
-- An error would be thrown
|
-- | Finding 'Cradle'.
|
||||||
findCradle :: Maybe FilePath -> String -> IO Cradle
|
-- An error would be thrown.
|
||||||
|
findCradle :: Maybe FilePath -- ^ A 'FilePath' for a sandbox
|
||||||
|
-> GHCVersion
|
||||||
|
-> IO Cradle
|
||||||
findCradle (Just sbox) strver = do
|
findCradle (Just sbox) strver = do
|
||||||
pkgConf <- checkPackageConf sbox strver
|
pkgConf <- checkPackageConf sbox strver
|
||||||
wdir <- getCurrentDirectory
|
wdir <- getCurrentDirectory
|
||||||
|
@ -14,10 +14,20 @@ import Prelude
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
debugInfo :: Options -> Cradle -> String -> FilePath -> IO String
|
-- | Obtaining debug information.
|
||||||
|
debugInfo :: Options
|
||||||
|
-> Cradle
|
||||||
|
-> GHCVersion
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> IO String
|
||||||
debugInfo opt cradle ver fileName = unlines <$> withGHC fileName (debug opt cradle ver fileName)
|
debugInfo opt cradle ver fileName = unlines <$> withGHC fileName (debug opt cradle ver fileName)
|
||||||
|
|
||||||
debug :: Options -> Cradle -> String -> FilePath -> Ghc [String]
|
-- | Obtaining debug information.
|
||||||
|
debug :: Options
|
||||||
|
-> Cradle
|
||||||
|
-> GHCVersion
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> Ghc [String]
|
||||||
debug opt cradle ver fileName = do
|
debug opt cradle ver fileName = do
|
||||||
(gopts, incDir, pkgs) <-
|
(gopts, incDir, pkgs) <-
|
||||||
if cabal then
|
if cabal then
|
||||||
|
@ -5,6 +5,8 @@ module Language.Haskell.GhcMod.Flag where
|
|||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified Language.Haskell.GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
|
|
||||||
|
-- | Listing GHC flags. (e.g -fno-warn-orphans)
|
||||||
|
|
||||||
listFlags :: Options -> IO String
|
listFlags :: Options -> IO String
|
||||||
listFlags opt = return $ convert opt [ "-f" ++ prefix ++ option
|
listFlags opt = return $ convert opt [ "-f" ++ prefix ++ option
|
||||||
| option <- Gap.fOptions
|
| option <- Gap.fOptions
|
||||||
|
@ -30,10 +30,15 @@ import System.IO
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
withGHCDummyFile :: Alternative m => Ghc (m a) -> IO (m a)
|
-- | Converting the 'Ghc' monad to the 'IO' monad.
|
||||||
|
withGHCDummyFile :: Alternative m => Ghc (m a) -- ^ 'Ghc' actions created by the Ghc utilities
|
||||||
|
-> IO (m a)
|
||||||
withGHCDummyFile = withGHC "Dummy"
|
withGHCDummyFile = withGHC "Dummy"
|
||||||
|
|
||||||
withGHC :: Alternative m => FilePath -> Ghc (m a) -> IO (m a)
|
-- | Converting the 'Ghc' monad to the 'IO' monad.
|
||||||
|
withGHC :: Alternative m => FilePath -- ^ A target file displayed in an error message
|
||||||
|
-> Ghc (m a) -- ^ 'Ghc' actions created by the Ghc utilities
|
||||||
|
-> IO (m a)
|
||||||
withGHC file body = ghandle ignore $ runGhc (Just libdir) $ do
|
withGHC file body = ghandle ignore $ runGhc (Just libdir) $ do
|
||||||
dflags <- getSessionDynFlags
|
dflags <- getSessionDynFlags
|
||||||
defaultCleanupHandler dflags body
|
defaultCleanupHandler dflags body
|
||||||
|
@ -1,7 +1,12 @@
|
|||||||
{-# LANGUAGE TupleSections, FlexibleInstances, TypeSynonymInstances #-}
|
{-# LANGUAGE TupleSections, FlexibleInstances, TypeSynonymInstances #-}
|
||||||
{-# LANGUAGE Rank2Types #-}
|
{-# LANGUAGE Rank2Types #-}
|
||||||
|
|
||||||
module Language.Haskell.GhcMod.Info (infoExpr, info, typeExpr, typeOf) where
|
module Language.Haskell.GhcMod.Info (
|
||||||
|
infoExpr
|
||||||
|
, info
|
||||||
|
, typeExpr
|
||||||
|
, typeOf
|
||||||
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Control.Monad (void, when)
|
import Control.Monad (void, when)
|
||||||
@ -29,19 +34,28 @@ import TcRnTypes
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
type Expression = String
|
|
||||||
type ModuleString = String
|
|
||||||
|
|
||||||
data Cmd = Info | Type deriving Eq
|
data Cmd = Info | Type deriving Eq
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
infoExpr :: Options -> Cradle -> ModuleString -> Expression -> FilePath -> IO String
|
-- | Obtaining information of a target expression. (GHCi's info:)
|
||||||
infoExpr opt cradle modstr expr file = (++ "\n") <$> withGHCDummyFile (info opt cradle file modstr expr)
|
infoExpr :: Options
|
||||||
|
-> Cradle
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> ModuleString -- ^ A module name
|
||||||
|
-> Expression -- ^ A Haskell expression
|
||||||
|
-> IO String
|
||||||
|
infoExpr opt cradle file modstr expr = (++ "\n") <$> withGHCDummyFile (info opt cradle file modstr expr)
|
||||||
|
|
||||||
info :: Options -> Cradle -> FilePath -> ModuleString -> Expression -> Ghc String
|
-- | Obtaining information of a target expression. (GHCi's info:)
|
||||||
info opt cradle fileName modstr expr =
|
info :: Options
|
||||||
inModuleContext Info opt cradle fileName modstr exprToInfo "Cannot show info"
|
-> Cradle
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> ModuleString -- ^ A module name
|
||||||
|
-> Expression -- ^ A Haskell expression
|
||||||
|
-> Ghc String
|
||||||
|
info opt cradle file modstr expr =
|
||||||
|
inModuleContext Info opt cradle file modstr exprToInfo "Cannot show info"
|
||||||
where
|
where
|
||||||
exprToInfo = infoThing expr
|
exprToInfo = infoThing expr
|
||||||
|
|
||||||
@ -67,12 +81,28 @@ instance HasType (LHsBind Id) where
|
|||||||
instance HasType (LPat Id) where
|
instance HasType (LPat Id) where
|
||||||
getType _ (L spn pat) = return $ Just (spn, hsPatType pat)
|
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 = withGHCDummyFile $ typeOf opt cradle file modstr lineNo colNo
|
|
||||||
|
|
||||||
typeOf :: Options -> Cradle -> FilePath -> ModuleString -> Int -> Int -> Ghc String
|
-- | Obtaining type of a target expression. (GHCi's type:)
|
||||||
typeOf opt cradle fileName modstr lineNo colNo =
|
typeExpr :: Options
|
||||||
inModuleContext Type opt cradle fileName modstr exprToType errmsg
|
-> Cradle
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> ModuleString -- ^ A odule name
|
||||||
|
-> Int -- ^ Line number
|
||||||
|
-> Int -- ^ Column number
|
||||||
|
-> IO String
|
||||||
|
typeExpr opt cradle file modstr lineNo colNo = withGHCDummyFile $ typeOf opt cradle file modstr lineNo colNo
|
||||||
|
|
||||||
|
-- | Obtaining type of a target expression. (GHCi's type:)
|
||||||
|
typeOf :: Options
|
||||||
|
-> Cradle
|
||||||
|
-> FilePath -- ^ A target file
|
||||||
|
-> ModuleString -- ^ A odule name
|
||||||
|
-> Int -- ^ Line number
|
||||||
|
-> Int -- ^ Column number
|
||||||
|
-> Ghc String
|
||||||
|
typeOf opt cradle file modstr lineNo colNo =
|
||||||
|
inModuleContext Type opt cradle file modstr exprToType errmsg
|
||||||
where
|
where
|
||||||
exprToType = do
|
exprToType = do
|
||||||
modSum <- getModSummary $ mkModuleName modstr
|
modSum <- getModSummary $ mkModuleName modstr
|
||||||
@ -142,13 +172,13 @@ pprInfo pefas (thing, fixity, insts)
|
|||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
inModuleContext :: Cmd -> Options -> Cradle -> FilePath -> ModuleString -> Ghc String -> String -> Ghc String
|
inModuleContext :: Cmd -> Options -> Cradle -> FilePath -> ModuleString -> Ghc String -> String -> Ghc String
|
||||||
inModuleContext cmd opt cradle fileName modstr action errmsg =
|
inModuleContext cmd opt cradle file modstr action errmsg =
|
||||||
valid ||> invalid ||> return errmsg
|
valid ||> invalid ||> return errmsg
|
||||||
where
|
where
|
||||||
valid = do
|
valid = do
|
||||||
void $ initializeFlagsWithCradle opt cradle ["-w:"] False
|
void $ initializeFlagsWithCradle opt cradle ["-w:"] False
|
||||||
when (cmd == Info) setSlowDynFlags
|
when (cmd == Info) setSlowDynFlags
|
||||||
setTargetFile fileName
|
setTargetFile file
|
||||||
checkSlowAndSet
|
checkSlowAndSet
|
||||||
void $ load LoadAllTargets
|
void $ load LoadAllTargets
|
||||||
doif setContextFromTarget action
|
doif setContextFromTarget action
|
||||||
|
@ -3,5 +3,7 @@ module Language.Haskell.GhcMod.Lang where
|
|||||||
import qualified Language.Haskell.GhcMod.Gap as Gap
|
import qualified Language.Haskell.GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
|
|
||||||
|
-- | Listing language extensions.
|
||||||
|
|
||||||
listLanguages :: Options -> IO String
|
listLanguages :: Options -> IO String
|
||||||
listLanguages opt = return $ convert opt Gap.supportedExtensions
|
listLanguages opt = return $ convert opt Gap.supportedExtensions
|
||||||
|
@ -5,10 +5,16 @@ import Data.List
|
|||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
import Language.Haskell.HLint
|
import Language.Haskell.HLint
|
||||||
|
|
||||||
lintSyntax :: Options -> String -> IO String
|
-- | Checking syntax of a target file using hlint.
|
||||||
|
-- Warnings and errors are returned.
|
||||||
|
lintSyntax :: Options
|
||||||
|
-> FilePath -- ^ A target file.
|
||||||
|
-> IO String
|
||||||
lintSyntax opt file = pack <$> lint opt file
|
lintSyntax opt file = pack <$> lint opt file
|
||||||
where
|
where
|
||||||
pack = unlines . map (intercalate "\0" . lines)
|
pack = unlines . map (intercalate "\0" . lines)
|
||||||
|
|
||||||
lint :: Options -> String -> IO [String]
|
lint :: Options
|
||||||
|
-> FilePath -- ^ A target file.
|
||||||
|
-> IO [String]
|
||||||
lint opt file = map show <$> hlint ([file, "--quiet"] ++ hlintOpts opt)
|
lint opt file = map show <$> hlint ([file, "--quiet"] ++ hlintOpts opt)
|
||||||
|
@ -1,4 +1,4 @@
|
|||||||
module Language.Haskell.GhcMod.List (listModules, list) where
|
module Language.Haskell.GhcMod.List (listModules, listMods) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.List
|
import Data.List
|
||||||
@ -10,11 +10,13 @@ import UniqFM
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
-- | Listing installed modules.
|
||||||
listModules :: Options -> IO String
|
listModules :: Options -> IO String
|
||||||
listModules opt = convert opt . nub . sort <$> withGHCDummyFile (list opt)
|
listModules opt = convert opt . nub . sort <$> withGHCDummyFile (listMods opt)
|
||||||
|
|
||||||
list :: Options -> Ghc [String]
|
-- | Listing installed modules.
|
||||||
list opt = do
|
listMods :: Options -> Ghc [String]
|
||||||
|
listMods opt = do
|
||||||
initializeFlags opt
|
initializeFlags opt
|
||||||
getExposedModules <$> getSessionDynFlags
|
getExposedModules <$> getSessionDynFlags
|
||||||
where
|
where
|
||||||
|
@ -2,18 +2,24 @@
|
|||||||
|
|
||||||
module Language.Haskell.GhcMod.Types where
|
module Language.Haskell.GhcMod.Types where
|
||||||
|
|
||||||
data OutputStyle = LispStyle | PlainStyle
|
-- | Output style.
|
||||||
|
data OutputStyle = LispStyle -- ^ S expression style
|
||||||
|
| PlainStyle -- ^ Plain textstyle
|
||||||
|
|
||||||
data Options = Options {
|
data Options = Options {
|
||||||
outputStyle :: OutputStyle
|
outputStyle :: OutputStyle
|
||||||
, hlintOpts :: [String]
|
, hlintOpts :: [String]
|
||||||
, ghcOpts :: [String]
|
, ghcOpts :: [String]
|
||||||
, operators :: Bool
|
, operators :: Bool
|
||||||
|
-- | If 'True', 'browse' also returns types.
|
||||||
, detailed :: Bool
|
, detailed :: Bool
|
||||||
|
-- | Whether or not Template Haskell should be expanded.
|
||||||
, expandSplice :: Bool
|
, expandSplice :: Bool
|
||||||
, sandbox :: Maybe String
|
-- | The sandbox directory.
|
||||||
|
, sandbox :: Maybe FilePath
|
||||||
}
|
}
|
||||||
|
|
||||||
|
-- | A default 'Options'.
|
||||||
defaultOptions :: Options
|
defaultOptions :: Options
|
||||||
defaultOptions = Options {
|
defaultOptions = Options {
|
||||||
outputStyle = PlainStyle
|
outputStyle = PlainStyle
|
||||||
@ -64,10 +70,15 @@ addNewLine = (++ "\n")
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
-- | The environment where this library is used
|
||||||
data Cradle = Cradle {
|
data Cradle = Cradle {
|
||||||
|
-- | The directory where this library is executed
|
||||||
cradleCurrentDir :: FilePath
|
cradleCurrentDir :: FilePath
|
||||||
|
-- | The directory where a cabal file is found
|
||||||
, cradleCabalDir :: Maybe FilePath
|
, cradleCabalDir :: Maybe FilePath
|
||||||
|
-- | The file name of the found cabal file
|
||||||
, cradleCabalFile :: Maybe FilePath
|
, cradleCabalFile :: Maybe FilePath
|
||||||
|
-- | The sandbox directory (e.g. \"\/foo\/bar\/packages-\<ver\>.conf/\")
|
||||||
, cradlePackageConf :: Maybe FilePath
|
, cradlePackageConf :: Maybe FilePath
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
@ -77,4 +88,13 @@ type GHCOption = String
|
|||||||
type IncludeDir = FilePath
|
type IncludeDir = FilePath
|
||||||
type Package = String
|
type Package = String
|
||||||
|
|
||||||
|
-- | GHC version in 'String'
|
||||||
|
type GHCVersion = String
|
||||||
|
|
||||||
|
-- | Haskell expression
|
||||||
|
type Expression = String
|
||||||
|
|
||||||
|
-- | Module name
|
||||||
|
type ModuleString = String
|
||||||
|
|
||||||
data CheckSpeed = Slow | Fast
|
data CheckSpeed = Slow | Fast
|
||||||
|
@ -96,8 +96,8 @@ main = flip catches handlers $ do
|
|||||||
"check" -> checkSyntax opt cradle cmdArg1
|
"check" -> checkSyntax opt cradle cmdArg1
|
||||||
"expand" -> checkSyntax opt { expandSplice = True } cradle cmdArg1
|
"expand" -> checkSyntax opt { expandSplice = True } cradle cmdArg1
|
||||||
"debug" -> debugInfo opt cradle strVer cmdArg1
|
"debug" -> debugInfo opt cradle strVer cmdArg1
|
||||||
"type" -> typeExpr opt cradle cmdArg2 (read cmdArg3) (read cmdArg4) cmdArg1
|
"type" -> typeExpr opt cradle cmdArg1 cmdArg2 (read cmdArg3) (read cmdArg4)
|
||||||
"info" -> infoExpr opt cradle cmdArg2 cmdArg3 cmdArg1
|
"info" -> infoExpr opt cradle cmdArg1 cmdArg2 cmdArg3
|
||||||
"lint" -> withFile (lintSyntax opt) cmdArg1
|
"lint" -> withFile (lintSyntax opt) cmdArg1
|
||||||
"lang" -> listLanguages opt
|
"lang" -> listLanguages opt
|
||||||
"flag" -> listFlags opt
|
"flag" -> listFlags opt
|
||||||
|
@ -14,38 +14,38 @@ spec = do
|
|||||||
withDirectory_ "test/data/ghc-mod-check" $ do
|
withDirectory_ "test/data/ghc-mod-check" $ do
|
||||||
(strVer,_) <- getGHCVersion
|
(strVer,_) <- getGHCVersion
|
||||||
cradle <- findCradle Nothing strVer
|
cradle <- findCradle Nothing strVer
|
||||||
res <- typeExpr defaultOptions cradle "Data.Foo" 9 5 "Data/Foo.hs"
|
res <- typeExpr defaultOptions cradle "Data/Foo.hs" "Data.Foo" 9 5
|
||||||
res `shouldBe` "9 5 11 40 \"Int -> a -> a -> a\"\n7 1 11 40 \"Int -> Integer\"\n"
|
res `shouldBe` "9 5 11 40 \"Int -> a -> a -> a\"\n7 1 11 40 \"Int -> Integer\"\n"
|
||||||
|
|
||||||
it "works with a module using TemplateHaskell" $ do
|
it "works with a module using TemplateHaskell" $ do
|
||||||
withDirectory_ "test/data" $ do
|
withDirectory_ "test/data" $ do
|
||||||
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
||||||
res <- typeExpr defaultOptions cradle "Bar" 5 1 "Bar.hs"
|
res <- typeExpr defaultOptions cradle "Bar.hs" "Bar" 5 1
|
||||||
res `shouldBe` unlines ["5 1 5 20 \"[Char]\""]
|
res `shouldBe` unlines ["5 1 5 20 \"[Char]\""]
|
||||||
|
|
||||||
it "works with a module that imports another module using TemplateHaskell" $ do
|
it "works with a module that imports another module using TemplateHaskell" $ do
|
||||||
withDirectory_ "test/data" $ do
|
withDirectory_ "test/data" $ do
|
||||||
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
||||||
res <- typeExpr defaultOptions cradle "Main" 3 8 "Main.hs"
|
res <- typeExpr defaultOptions cradle "Main.hs" "Main" 3 8
|
||||||
res `shouldBe` unlines ["3 8 3 16 \"String -> IO ()\"", "3 8 3 20 \"IO ()\"", "3 1 3 20 \"IO ()\""]
|
res `shouldBe` unlines ["3 8 3 16 \"String -> IO ()\"", "3 8 3 20 \"IO ()\"", "3 1 3 20 \"IO ()\""]
|
||||||
|
|
||||||
describe "infoExpr" $ do
|
describe "infoExpr" $ do
|
||||||
it "works for non-export functions" $ do
|
it "works for non-export functions" $ do
|
||||||
withDirectory_ "test/data" $ do
|
withDirectory_ "test/data" $ do
|
||||||
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
||||||
res <- infoExpr defaultOptions cradle "Info" "fib" "Info.hs"
|
res <- infoExpr defaultOptions cradle "Info.hs" "Info" "fib"
|
||||||
res `shouldSatisfy` ("fib :: Int -> Int" `isPrefixOf`)
|
res `shouldSatisfy` ("fib :: Int -> Int" `isPrefixOf`)
|
||||||
|
|
||||||
it "works with a module using TemplateHaskell" $ do
|
it "works with a module using TemplateHaskell" $ do
|
||||||
withDirectory_ "test/data" $ do
|
withDirectory_ "test/data" $ do
|
||||||
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
||||||
res <- infoExpr defaultOptions cradle "Bar" "foo" "Bar.hs"
|
res <- infoExpr defaultOptions cradle "Bar.hs" "Bar" "foo"
|
||||||
res `shouldSatisfy` ("foo :: ExpQ" `isPrefixOf`)
|
res `shouldSatisfy` ("foo :: ExpQ" `isPrefixOf`)
|
||||||
|
|
||||||
it "works with a module that imports another module using TemplateHaskell" $ do
|
it "works with a module that imports another module using TemplateHaskell" $ do
|
||||||
withDirectory_ "test/data" $ do
|
withDirectory_ "test/data" $ do
|
||||||
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
cradle <- getGHCVersion >>= findCradle Nothing . fst
|
||||||
res <- infoExpr defaultOptions cradle "Main" "bar" "Main.hs"
|
res <- infoExpr defaultOptions cradle "Main.hs" "Main" "bar"
|
||||||
res `shouldSatisfy` ("bar :: [Char]" `isPrefixOf`)
|
res `shouldSatisfy` ("bar :: [Char]" `isPrefixOf`)
|
||||||
|
|
||||||
it "doesn't fail on unicode output" $ do
|
it "doesn't fail on unicode output" $ do
|
||||||
|
Loading…
Reference in New Issue
Block a user