2013-05-18 21:16:37 +00:00
|
|
|
module Language.Haskell.GhcMod.Browse (browseModule, browse) where
|
2010-03-11 10:03:17 +00:00
|
|
|
|
2010-04-28 06:51:30 +00:00
|
|
|
import Control.Applicative
|
2013-09-27 03:25:41 +00:00
|
|
|
import Control.Monad (void)
|
2010-03-11 10:03:17 +00:00
|
|
|
import Data.Char
|
|
|
|
import Data.List
|
2013-11-17 18:31:47 +00:00
|
|
|
import Data.Maybe (catMaybes)
|
2013-03-12 13:15:23 +00:00
|
|
|
import DataCon (dataConRepType)
|
2013-10-29 16:48:27 +00:00
|
|
|
import FastString (mkFastString)
|
2010-04-28 06:51:30 +00:00
|
|
|
import GHC
|
2014-02-06 12:27:39 +00:00
|
|
|
import Panic (throwGhcException)
|
2013-07-14 08:07:30 +00:00
|
|
|
import Language.Haskell.GhcMod.Doc (showUnqualifiedPage)
|
2013-05-17 01:00:01 +00:00
|
|
|
import Language.Haskell.GhcMod.GHCApi
|
2014-02-06 12:34:40 +00:00
|
|
|
import Language.Haskell.GhcMod.Gap
|
2013-05-17 01:00:01 +00:00
|
|
|
import Language.Haskell.GhcMod.Types
|
2010-04-28 06:51:30 +00:00
|
|
|
import Name
|
2013-02-23 08:51:55 +00:00
|
|
|
import Outputable
|
|
|
|
import TyCon
|
|
|
|
import Type
|
2013-02-28 07:33:11 +00:00
|
|
|
import Var
|
2010-03-11 10:03:17 +00:00
|
|
|
|
|
|
|
----------------------------------------------------------------
|
|
|
|
|
2013-05-20 05:28:56 +00:00
|
|
|
-- | Getting functions, classes, etc from a module.
|
|
|
|
-- If 'detailed' is 'True', their types are also obtained.
|
2013-09-05 05:35:28 +00:00
|
|
|
-- If 'operators' is 'True', operators are also returned.
|
2013-05-20 05:28:56 +00:00
|
|
|
browseModule :: Options
|
2013-09-27 03:25:41 +00:00
|
|
|
-> Cradle
|
2013-05-20 05:28:56 +00:00
|
|
|
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
|
|
|
-> IO String
|
2013-11-17 18:31:47 +00:00
|
|
|
browseModule opt cradle mdlName = convert opt . sort <$> withGHCDummyFile (browse opt cradle mdlName)
|
2010-03-11 10:03:17 +00:00
|
|
|
|
2013-05-20 05:28:56 +00:00
|
|
|
-- | Getting functions, classes, etc from a module.
|
|
|
|
-- If 'detailed' is 'True', their types are also obtained.
|
2013-09-05 05:35:28 +00:00
|
|
|
-- If 'operators' is 'True', operators are also returned.
|
2013-05-20 05:28:56 +00:00
|
|
|
browse :: Options
|
2013-09-27 03:25:41 +00:00
|
|
|
-> Cradle
|
2013-05-20 05:28:56 +00:00
|
|
|
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
|
|
|
-> Ghc [String]
|
2013-09-27 03:25:41 +00:00
|
|
|
browse opt cradle mdlName = do
|
|
|
|
void $ initializeFlagsWithCradle opt cradle [] False
|
2013-03-01 01:16:31 +00:00
|
|
|
getModule >>= getModuleInfo >>= listExports
|
2010-04-27 01:28:00 +00:00
|
|
|
where
|
2013-11-20 05:28:20 +00:00
|
|
|
getModule = findModule mdlname mpkgid `gcatch` fallback
|
|
|
|
mdlname = mkModuleName mdlName
|
|
|
|
mpkgid = mkFastString <$> packageId opt
|
2013-03-01 01:16:31 +00:00
|
|
|
listExports Nothing = return []
|
2013-11-17 18:31:47 +00:00
|
|
|
listExports (Just mdinfo) = processExports opt mdinfo
|
2013-11-20 05:28:20 +00:00
|
|
|
-- findModule works only for package modules, moreover,
|
|
|
|
-- you cannot load a package module. On the other hand,
|
|
|
|
-- to browse a local module you need to load it first.
|
|
|
|
-- If CmdLineError is signalled, we assume the user
|
|
|
|
-- tried browsing a local module.
|
|
|
|
fallback (CmdLineError _) = loadAndFind
|
|
|
|
fallback e = throwGhcException e
|
2013-11-20 04:57:45 +00:00
|
|
|
loadAndFind = do
|
|
|
|
setTargetFiles [mdlName]
|
|
|
|
checkSlowAndSet
|
|
|
|
void $ load LoadAllTargets
|
2013-11-20 05:28:20 +00:00
|
|
|
findModule mdlname Nothing
|
2013-02-23 08:51:55 +00:00
|
|
|
|
2013-11-17 18:31:47 +00:00
|
|
|
processExports :: Options -> ModuleInfo -> Ghc [String]
|
|
|
|
processExports opt minfo = mapM (showExport opt minfo) $ removeOps $ modInfoExports minfo
|
|
|
|
where
|
|
|
|
removeOps
|
|
|
|
| operators opt = id
|
|
|
|
| otherwise = filter (isAlpha . head . getOccString)
|
2013-02-23 08:51:55 +00:00
|
|
|
|
2013-11-17 18:31:47 +00:00
|
|
|
showExport :: Options -> ModuleInfo -> Name -> Ghc String
|
|
|
|
showExport opt minfo e = do
|
|
|
|
mtype' <- mtype
|
|
|
|
return $ concat $ catMaybes [mqualified, Just $ formatOp $ getOccString e, mtype']
|
2013-02-28 17:24:14 +00:00
|
|
|
where
|
2013-11-18 14:22:49 +00:00
|
|
|
mqualified = (moduleNameString (moduleName $ nameModule e) ++ ".") `justIf` qualified opt
|
2013-11-17 18:31:47 +00:00
|
|
|
mtype
|
|
|
|
| detailed opt = do
|
|
|
|
tyInfo <- modInfoLookupName minfo e
|
2013-02-28 17:24:14 +00:00
|
|
|
-- If nothing found, load dependent module and lookup global
|
2013-11-17 18:31:47 +00:00
|
|
|
tyResult <- maybe (inOtherModule e) (return . Just) tyInfo
|
2013-03-12 13:15:23 +00:00
|
|
|
dflag <- getSessionDynFlags
|
2013-11-17 18:31:47 +00:00
|
|
|
return $ do
|
|
|
|
typeName <- tyResult >>= showThing dflag
|
|
|
|
(" :: " ++ typeName) `justIf` detailed opt
|
|
|
|
| otherwise = return Nothing
|
|
|
|
formatOp nm@(n:_)
|
|
|
|
| isAlpha n = nm
|
|
|
|
| otherwise = "(" ++ nm ++ ")"
|
|
|
|
formatOp "" = error "formatOp"
|
2013-02-28 17:24:14 +00:00
|
|
|
inOtherModule :: Name -> Ghc (Maybe TyThing)
|
2013-03-01 01:16:31 +00:00
|
|
|
inOtherModule nm = getModuleInfo (nameModule nm) >> lookupGlobalName nm
|
2013-11-17 18:31:47 +00:00
|
|
|
justIf :: a -> Bool -> Maybe a
|
|
|
|
justIf x True = Just x
|
|
|
|
justIf _ False = Nothing
|
2013-02-23 08:51:55 +00:00
|
|
|
|
2013-03-12 13:15:23 +00:00
|
|
|
showThing :: DynFlags -> TyThing -> Maybe String
|
2014-02-06 12:34:40 +00:00
|
|
|
showThing dflag tything = showThing' dflag (fromTyThing tything)
|
|
|
|
|
|
|
|
showThing' :: DynFlags -> GapThing -> Maybe String
|
|
|
|
showThing' dflag (GtI i) = Just $ formatType dflag varType i
|
|
|
|
showThing' dflag (GtD d) = Just $ formatType dflag dataConRepType d
|
|
|
|
showThing' _ (GtT t) = unwords . toList <$> tyType t
|
2013-02-28 17:24:14 +00:00
|
|
|
where
|
2013-03-01 01:16:31 +00:00
|
|
|
toList t' = t' : getOccString t : map getOccString (tyConTyVars t)
|
2014-02-06 12:34:40 +00:00
|
|
|
showThing' _ _ = Nothing
|
2013-03-01 01:16:31 +00:00
|
|
|
|
2013-03-12 13:15:23 +00:00
|
|
|
formatType :: NamedThing a => DynFlags -> (a -> Type) -> a -> String
|
2013-11-17 18:31:47 +00:00
|
|
|
formatType dflag f x = showOutputable dflag (removeForAlls $ f x)
|
2013-03-01 13:11:02 +00:00
|
|
|
|
2013-03-01 01:16:31 +00:00
|
|
|
tyType :: TyCon -> Maybe String
|
|
|
|
tyType typ
|
|
|
|
| isAlgTyCon typ
|
|
|
|
&& not (isNewTyCon typ)
|
|
|
|
&& not (isClassTyCon typ) = Just "data"
|
|
|
|
| isNewTyCon typ = Just "newtype"
|
|
|
|
| isClassTyCon typ = Just "class"
|
|
|
|
| isSynTyCon typ = Just "type"
|
|
|
|
| otherwise = Nothing
|
2013-02-23 08:51:55 +00:00
|
|
|
|
2013-02-28 17:24:14 +00:00
|
|
|
removeForAlls :: Type -> Type
|
2013-03-01 01:16:31 +00:00
|
|
|
removeForAlls ty = removeForAlls' ty' tty'
|
2013-02-28 17:24:14 +00:00
|
|
|
where
|
2013-03-01 01:16:31 +00:00
|
|
|
ty' = dropForAlls ty
|
|
|
|
tty' = splitFunTy_maybe ty'
|
|
|
|
|
|
|
|
removeForAlls' :: Type -> Maybe (Type, Type) -> Type
|
|
|
|
removeForAlls' ty Nothing = ty
|
|
|
|
removeForAlls' ty (Just (pre, ftype))
|
|
|
|
| isPredTy pre = mkFunTy pre (dropForAlls ftype)
|
|
|
|
| otherwise = ty
|
2013-02-23 08:51:55 +00:00
|
|
|
|
2013-03-12 13:15:23 +00:00
|
|
|
showOutputable :: Outputable a => DynFlags -> a -> String
|
2013-07-14 08:07:30 +00:00
|
|
|
showOutputable dflag = unwords . lines . showUnqualifiedPage dflag . ppr
|