Skip to content

Commit

Permalink
show doc in browse command for froogle
Browse files Browse the repository at this point in the history
  • Loading branch information
mmhelloworld committed Jan 18, 2016
1 parent 4fe3302 commit db0e8a3
Show file tree
Hide file tree
Showing 3 changed files with 54 additions and 11 deletions.
2 changes: 1 addition & 1 deletion build.gradle
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ subprojects {
isSnapshot = true
snapshotAppendix = "-SNAPSHOT"
projectVersion = baseVersion + (isSnapshot ? snapshotAppendix : "")
fregeVersion = "3.23.370-g898bc8c"
fregeVersion = "3.23.450-SNAPSHOT"
}

apply from: "$rootDir/gradle/sonatype.gradle"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,8 @@ import Compiler.types.SNames
import Compiler.types.Types
import Compiler.passes.Imp (importClass)
import Compiler.classes.Nice(Nice, category)
import Compiler.common.Errors as E()
import Compiler.common.Resolve as R
import Compiler.common.Types as CommonTypes(instanceHead)

import Compiler.grammar.Lexer as L()
import Compiler.grammar.Frege as F()
Expand All @@ -53,7 +53,7 @@ import Control.monad.trans.MonadIO
import Control.monad.trans.MonadTrans
import Control.arrow.Kleisli

import Ide.Utilities as Util
import Ide.Utilities as Util (verbose, symbolDocumentation, packDocumentation, symbols)

import Java.Net (URLClassLoader)

Expand Down Expand Up @@ -216,12 +216,12 @@ run src predefs steps = do
ExpressionSource -> return $ SourceInfo.Expression <$> listToMaybe generatedSym
else return Nothing

browseModule :: String -> Interpreter (Maybe ([Symbol], Global))
browseModule :: String -> Interpreter (Maybe (String, [Symbol], Global))
browseModule moduleName = do
state <- Interpreter.get
(g, srcInfo) <- typecheck "\"\""
syms <- liftIO $ StateT.run (browseSymbols moduleName) g
return $ maybe Nothing (const $ Just syms) srcInfo
(moduleDoc, g) <- liftIO $ (Imp.getFP (magicPack moduleName)).run g
(syms, g) <- liftIO $ StateT.run (browseSymbols moduleName) g
return $ maybe Nothing (const $ Just (either (const "") (maybe "" _.doc) moduleDoc, syms, g)) srcInfo

browse :: String -> Interpreter (Maybe ([Symbol], Global))
browse src = do
Expand Down Expand Up @@ -362,7 +362,7 @@ getEnv g q = g.find q >>= symEnv
| otherwise = Nothing

outlineSymbols :: Global -> [String]
outlineSymbols g = map (Util.label g) $ Util.symbols g.thisTab
outlineSymbols g = map (show . label g) $ Util.symbols g.thisTab

newLine = maybe "\n" id $ System.getProperty "line.separator"

Expand Down Expand Up @@ -530,7 +530,51 @@ getSymbolType g sym
| otherwise = ""

showSymbol :: Global -> Symbol -> String
showSymbol g sym = category sym g ++ " " ++ Util.label g sym
showSymbol g s = show $ label g s

data Signature =
FuncSig { name :: String, typ :: String, doc :: Maybe String}
| DataSig { name :: String, typ :: String, doc :: Maybe String }
| TypeAliasSig { name :: String, typ :: String, doc :: Maybe String }
| InstanceSig { name :: String, doc :: Maybe String }
| ClassSig { name :: String, kind :: String, doc :: Maybe String }
| UnknownSig { name :: String, category :: String, doc :: Maybe String }

instance Show Signature where
show (FuncSig name typ doc) = (showDoc doc) ++ "\n" ++ addParensForOperators name ++ " :: " ++ typ
show (DataSig name typ doc) = (showDoc doc) ++ "\ndata " ++ addParensForOperators name --++ " :: " ++ typ Commented for hoogle
show (TypeAliasSig name typ doc) = (showDoc doc) ++ "\ntype " ++ addParensForOperators name ++ " = " ++ typ
show (InstanceSig name doc) = (showDoc doc) ++ "\ninstance " ++ addParensForOperators name
show (ClassSig name kind doc) = (showDoc doc) ++ "\nclass " ++ addParensForOperators name --++ " :: " ++ kind
show (UnknownSig name category doc) = (showDoc doc) ++ "\n" ++ category ++ " " ++ addParensForOperators name

private addParensForOperators s
| s !~ '\p{L}' = "(" ++ s ++ ")"
| otherwise = s

private showDoc doc = maybe "" prefixCommentChars doc

prefixCommentChars doc = "-- | " ++ (intercalate "\n-- " $ dropWhile (null . trim) $ lines doc)

label Global Symbol Signature
label g SymI{clas,typ, doc} = InstanceSig (nicer (instanceHead clas typ.rho) g) doc
label g SymV{name,typ, doc} = FuncSig name.base (verbose g typ) doc
label g SymD{name,typ, doc} = FuncSig name.base (verbose g typ) doc
label g SymC{name,tau, doc} = ClassSig name.base (show tau.kind) doc
label g SymT{name, nativ = Just n, pur, mutable, doc}
| pur = DataSig name.base ("pure native " ++ n) doc
| mutable = DataSig name.base ("mutable native " ++ n) doc
| otherwise = DataSig name.base ("native " ++ n) doc
label g SymA{name,typ, doc} = TypeAliasSig name.base (typ.rho.nicer gspecial) doc
where
gspecial = g.{options <- _.{flags <- Flags.flagSet SPECIAL}}
label g sym
| sym.{kind?} = DataSig sym.name.base (show sym.kind) sym.doc
| sym.{alias?} =
let f aliasSym = info.{name = sym.name.base} where
info = label g aliasSym
in maybe (UnknownSig sym.name.base (category sym g) sym.doc) f $ g.find sym.alias
| otherwise = UnknownSig sym.name.base (category sym g) sym.doc

getSymbols :: Symtab -> [Symbol]
getSymbols tab = (sortBy positionAndName filter wanted values) tab
Expand Down Expand Up @@ -672,5 +716,6 @@ data Method = pure native java.lang.reflect.Method where
pure native getName :: Method -> String

pure native split :: String -> String -> JArray String
pure native trim :: String -> String

native asURLClassLoader "(java.net.URLClassLoader)" :: MutableIO InterpreterClassLoader -> IO URLClassLoader
Original file line number Diff line number Diff line change
Expand Up @@ -368,8 +368,6 @@ data CompiledScript = native javax.script.CompiledScript
native createFregeCompiledScript FregeScriptEngine.newFregeCompiledScript
:: String -> Mutable s ScriptEngine -> InterpreterConfig -> InterpreterResult -> Mutable s InterpreterClassLoader -> STMutable s CompiledScript

pure native trim :: String -> String

fregePreludeScriptKey = "frege.scriptengine.preludeScript"
classLoaderKey = "frege.scriptengine.classloader"
configKey = "frege.scriptengine.currentDefs"
Expand Down

0 comments on commit db0e8a3

Please sign in to comment.