Skip to content

Instantly share code, notes, and snippets.

@eagletmt
Created August 8, 2010 00:01
Show Gist options
  • Save eagletmt/513359 to your computer and use it in GitHub Desktop.
Save eagletmt/513359 to your computer and use it in GitHub Desktop.
export されている名前とその型を表示
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Maybe (mapMaybe)
import Data.List (sort)
import Control.Applicative ((<$>))
import Control.Monad (unless)
import Control.Exception (SomeException)
import System.Environment (getArgs)
import GHC
import GHC.Paths (libdir)
import Outputable (ppr, defaultUserStyle)
import Pretty (showDocWith, Mode(OneLineMode))
import Var (varType)
import Name (getOccString)
main :: IO ()
main = do
args <- getArgs
unless (null args)
$ browseType (head args) >>= mapM_ (\(i,t) -> putStrLn (i ++ " = " ++ t)) . sort
browseType :: String -> IO [(String, String)]
browseType modName = runGhc (Just libdir) $ do
getSessionDynFlags >>= setSessionDynFlags
exports <- maybe [] modInfoExports <$>
(findModule (mkModuleName modName) Nothing >>= getModuleInfo)
`gcatch` (\(_::SomeException) -> return Nothing)
mapMaybe (>>= idAndType) <$> mapM lookupName exports
where
idAndType :: TyThing -> Maybe (String,String)
idAndType (AnId v) = Just (getOccString v, showSDocOneLine (ppr (varType v)))
idAndType (ADataCon d) = Just (getOccString d, showSDocOneLine (ppr (dataConType d)))
idAndType _ = Nothing
showSDocOneLine d = showDocWith OneLineMode (d defaultUserStyle)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment