Add back --debug flag, only generate debugger in that case

This commit is contained in:
Evan Czaplicki 2018-04-08 14:22:39 +02:00
parent a36152c14d
commit 6585f1faff
10 changed files with 171 additions and 97 deletions

View File

@ -11,6 +11,7 @@ import qualified Elm.Compiler.Module as Module
import qualified Elm.Project.Json as Project
import qualified Elm.Project.Summary as Summary
import qualified Reporting.Exit as Exit
import qualified Reporting.Exit.Make as E
import qualified Reporting.Task as Task
@ -36,4 +37,4 @@ fromSummary (Summary.Summary _ project _ _ _) =
return $ Pkg (Project.getExposed info)
Project.App _ ->
Task.throw Exit.CannotMakeNothing
Task.throw (Exit.Make E.CannotMakeNothing)

View File

@ -34,6 +34,7 @@ import qualified Generate.Functions as Functions
import qualified Generate.Html as Html
import qualified Generate.Nitpick as Nitpick
import qualified Reporting.Exit as Exit
import qualified Reporting.Exit.Make as E
import qualified Reporting.Task as Task
import qualified Stuff.Paths as Paths
import Terminal.Args (Parser(..), suggestFiles)
@ -61,6 +62,7 @@ generate options summary graph@(Crawl.Graph args _ _ _ _) =
do objectGraph <- organize summary graph
case _mode options of
Obj.Debug -> return ()
Obj.Dev -> return ()
Obj.Prod -> noDebugUses summary objectGraph
@ -163,7 +165,7 @@ noDebugUses (Summary.Summary _ project _ _ _) graph =
return ()
m:ms ->
Task.throw (Exit.CannotOptimizeDebug m ms)
Task.throw (Exit.Make (E.CannotOptimizeDebugValues m ms))
noDebugUsesInPackage :: Summary.Summary -> Crawl.Result -> Task.Task ()

View File

@ -21,6 +21,7 @@ import qualified Reporting.Exit.Deps as Deps
import qualified Reporting.Exit.Diff as Diff
import qualified Reporting.Exit.Help as Help
import qualified Reporting.Exit.Http as Http
import qualified Reporting.Exit.Make as Make
import qualified Reporting.Exit.Publish as Publish
@ -37,13 +38,12 @@ data Exit
| Cycle [Module.Raw] -- TODO write docs to help with this scenario
| Deps Deps.Exit
| Diff Diff.Exit
| Make Make.Exit
| Publish Publish.Exit
| BadHttp String Http.Exit
-- misc
| NoSolution [Pkg.Name]
| CannotMakeNothing
| CannotOptimizeDebug Module.Raw [Module.Raw]
@ -86,17 +86,17 @@ toReport exit =
"Whatever your scenario, I hope you have a lovely time using Elm!"
]
Assets assetError ->
Asset.toReport assetError
Assets assetExit ->
Asset.toReport assetExit
Bump bumpError ->
Bump.toReport bumpError
Bump bumpExit ->
Bump.toReport bumpExit
Compile e es ->
Help.compilerReport e es
Crawl crawlError ->
Crawl.toReport crawlError
Crawl crawlExit ->
Crawl.toReport crawlExit
Cycle names ->
Help.report "IMPORT CYCLE" Nothing
@ -107,17 +107,20 @@ toReport exit =
++ D.makeLink "import-cycles"
]
Deps depsError ->
Deps.toReport depsError
Deps depsExit ->
Deps.toReport depsExit
Diff commandsError ->
Diff.toReport commandsError
Diff commandsExit ->
Diff.toReport commandsExit
Publish publishError ->
Publish.toReport publishError
Make makeExit ->
Make.toReport makeExit
BadHttp url httpError ->
Http.toReport url httpError
Publish publishExit ->
Publish.toReport publishExit
BadHttp url httpExit ->
Http.toReport url httpExit
NoSolution badPackages ->
case badPackages of
@ -148,36 +151,3 @@ toReport exit =
\ goals, etc. They face obstacles outside of their technical work you will never\
\ know about, so please assume the best and try to be patient and supportive!"
]
CannotMakeNothing ->
Help.report "NO INPUT" Nothing
"What should I make though? I need more information, like:"
[ D.vcat
[ D.indent 4 $ D.green "elm make MyThing.elm"
, D.indent 4 $ D.green "elm make This.elm That.elm"
]
, D.reflow
"However many files you give, I will create one JS file out of them."
]
CannotOptimizeDebug m ms ->
Help.report "DEBUG REMNANTS" Nothing
"There are uses of the `Debug` module in the following modules:"
[ D.indent 4 $ D.red $ D.vcat $ map (D.fromString . Module.nameToString) (m:ms)
, D.reflow "But the --optimize flag only works if all `Debug` functions are removed!"
, D.toSimpleNote $
"The issue is that --optimize strips out info needed by `Debug` functions.\
\ Here are two examples:"
, D.indent 4 $ D.reflow $
"(1) It shortens record field names. This makes the generated JavaScript is\
\ smaller, but `Debug.toString` cannot know the real field names anymore."
, D.indent 4 $ D.reflow $
"(2) Values like `type Height = Height Float` are unboxed. This reduces\
\ allocation, but it also means that `Debug.toString` cannot tell if it is\
\ looking at a `Height` or `Float` value."
, D.reflow $
"There are a few other cases like that, and it will be much worse once we start\
\ inlining code. That optimization could move `Debug.log` and `Debug.todo` calls,\
\ resulting in unpredictable behavior. I hope that clarifies why this restriction\
\ exists!"
]

View File

@ -0,0 +1,75 @@
{-# LANGUAGE OverloadedStrings #-}
module Reporting.Exit.Make
( Exit(..)
, toReport
)
where
import qualified Elm.Compiler.Module as Module
import qualified Reporting.Doc as D
import qualified Reporting.Exit.Help as Help
-- EXITS
data Exit
= CannotMakeNothing
| CannotOptimizeDebugValues Module.Raw [Module.Raw]
| CannotOptimizeAndDebug
-- TO REPORT
toReport :: Exit -> Help.Report
toReport exit =
case exit of
CannotMakeNothing ->
Help.report "NO INPUT" Nothing
"What should I make though? I need more information, like:"
[ D.vcat
[ D.indent 4 $ D.green "elm make MyThing.elm"
, D.indent 4 $ D.green "elm make This.elm That.elm"
]
, D.reflow
"However many files you give, I will create one JS file out of them."
]
CannotOptimizeDebugValues m ms ->
Help.report "DEBUG REMNANTS" Nothing
"There are uses of the `Debug` module in the following modules:"
[ D.indent 4 $ D.red $ D.vcat $ map (D.fromString . Module.nameToString) (m:ms)
, D.reflow "But the --optimize flag only works if all `Debug` functions are removed!"
, D.toSimpleNote $
"The issue is that --optimize strips out info needed by `Debug` functions.\
\ Here are two examples:"
, D.indent 4 $ D.reflow $
"(1) It shortens record field names. This makes the generated JavaScript is\
\ smaller, but `Debug.toString` cannot know the real field names anymore."
, D.indent 4 $ D.reflow $
"(2) Values like `type Height = Height Float` are unboxed. This reduces\
\ allocation, but it also means that `Debug.toString` cannot tell if it is\
\ looking at a `Height` or `Float` value."
, D.reflow $
"There are a few other cases like that, and it will be much worse once we start\
\ inlining code. That optimization could move `Debug.log` and `Debug.todo` calls,\
\ resulting in unpredictable behavior. I hope that clarifies why this restriction\
\ exists!"
]
CannotOptimizeAndDebug ->
Help.docReport "CLASHING FLAGS" Nothing
( D.fillSep
["I","cannot","compile","with",D.red "--optimize","and"
,D.red "--debug","at","the","same","time."
]
)
[ D.reflow
"I need to take away information to optimize things, and I need to\
\ add information to add the debugger. It is impossible to do both\
\ at once, so pick just one of those flags."
]

View File

@ -36,7 +36,7 @@ import qualified Reporting.Doc as D
-- GENERATE MAINS
data Mode = Dev | Prod
data Mode = Prod | Dev | Debug
data Output
@ -71,8 +71,11 @@ addMain mode graph home _ state =
toRealMode :: Mode -> Name.Target -> Map.Map N.Name Int -> Name.Mode
toRealMode mode target fields =
case mode of
Debug ->
Name.Dev target Name.DebuggerOn
Dev ->
Name.Dev target
Name.Dev target Name.DebuggerOff
Prod ->
Name.Prod target (Name.shortenFieldNames fields)
@ -85,7 +88,7 @@ toRealMode mode target fields =
generateForRepl :: Opt.Graph -> I.Interface -> ModuleName.Canonical -> N.Name -> B.Builder
generateForRepl (Opt.Graph _ graph _) iface home name =
let
mode = Name.Dev Name.Server
mode = Name.Dev Name.Server Name.DebuggerOff
debugState = addGlobal mode graph emptyState (Opt.Global ModuleName.debug "toString")
evalState = addGlobal mode graph debugState (Opt.Global home name)
in
@ -238,7 +241,7 @@ generateCycle mode (Opt.Global home _) cycle =
Name.Prod _ _ ->
block
Name.Dev _ ->
Name.Dev _ _ ->
JS.Try block Name.dollar $ JS.Throw $ JS.String $
"The following top-level definitions are causing infinite recursion:\\n"
<> drawCycle (map fst cycle)
@ -310,7 +313,7 @@ addChunk mode builder chunk =
Opt.Debug ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
builder
Name.Prod _ _ ->
@ -318,7 +321,7 @@ addChunk mode builder chunk =
Opt.Prod ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
"_UNUSED" <> builder
Name.Prod _ _ ->
@ -334,7 +337,7 @@ generateEnum mode (Opt.Global home name) ctorName index =
let
definition =
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
Expr.codeToExpr (Expr.generateCtor mode ctorName index 0)
Name.Prod _ _ ->
@ -352,7 +355,7 @@ generateBox mode (Opt.Global home name) ctorName =
let
definition =
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
Expr.codeToExpr (Expr.generateCtor mode ctorName Index.first 1)
Name.Prod _ _ ->

View File

@ -58,7 +58,7 @@ generate mode expression =
Opt.Chr char ->
JsExpr $
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
JS.Call toChar [ JS.String (Text.encodeUtf8Builder char) ]
Name.Prod _ _ ->
@ -81,7 +81,7 @@ generate mode expression =
Opt.VarEnum (Opt.Global home name) index ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
JsExpr $ JS.Ref (Name.fromGlobal home name)
Name.Prod _ _ ->
@ -90,7 +90,7 @@ generate mode expression =
Opt.VarBox (Opt.Global home name) ->
JsExpr $ JS.Ref $
case mode of
Name.Dev _ -> Name.fromGlobal home name
Name.Dev _ _ -> Name.fromGlobal home name
Name.Prod _ _ -> Name.fromGlobal ModuleName.basics N.identity
Opt.VarCycle home name ->
@ -161,7 +161,7 @@ generate mode expression =
Opt.Unit ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
JsExpr $ JS.Ref (Name.fromKernel N.utils "Tuple0")
Name.Prod _ _ ->
@ -261,7 +261,7 @@ generateCtor mode name index arity =
ctorTag =
case mode of
Name.Dev _ -> JS.String (N.toBuilder name)
Name.Dev _ _ -> JS.String (N.toBuilder name)
Name.Prod _ _ -> JS.Int (Index.toMachine index)
in
generateFunction argNames $ JsExpr $ JS.Object $
@ -363,7 +363,7 @@ generateCall mode func args =
Opt.VarBox _ ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
generateCallHelp mode func args
Name.Prod _ _ ->
@ -744,7 +744,7 @@ generatePath mode path =
Opt.Unbox subPath ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
JS.Access (generatePath mode subPath) (Name.fromIndex Index.first)
Name.Prod _ _ ->
@ -872,7 +872,7 @@ generateIfTest mode root (path, test) =
DT.IsCtor name index _ _ ->
strictEq (JS.Access value Name.dollar) $
case mode of
Name.Dev _ -> JS.String (N.toBuilder name)
Name.Dev _ _ -> JS.String (N.toBuilder name)
Name.Prod _ _ -> JS.Int (Index.toMachine index)
DT.IsInt int ->
@ -881,7 +881,7 @@ generateIfTest mode root (path, test) =
DT.IsChr char ->
strictEq (JS.String (Text.encodeUtf8Builder char)) $
case mode of
Name.Dev _ -> JS.Call (JS.Access value (Name.fromLocal "valueOf")) []
Name.Dev _ _ -> JS.Call (JS.Access value (Name.fromLocal "valueOf")) []
Name.Prod _ _ -> value
DT.IsStr string ->
@ -911,7 +911,7 @@ generateCaseValue mode test =
case test of
DT.IsCtor name index _ _ ->
case mode of
Name.Dev _ -> JS.String (N.toBuilder name)
Name.Dev _ _ -> JS.String (N.toBuilder name)
Name.Prod _ _ -> JS.Int (Index.toMachine index)
DT.IsInt int ->
@ -941,7 +941,7 @@ generateCaseTest mode root path exampleTest =
case exampleTest of
DT.IsCtor _ _ _ opts ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
JS.Access value Name.dollar
Name.Prod _ _ ->
@ -963,7 +963,7 @@ generateCaseTest mode root path exampleTest =
DT.IsChr _ ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
JS.Call (JS.Access value (Name.fromLocal "valueOf")) []
Name.Prod _ _ ->
@ -991,7 +991,7 @@ pathToJsExpr mode root path =
DT.Unbox subPath ->
case mode of
Name.Dev _ ->
Name.Dev _ _ ->
JS.Access (pathToJsExpr mode root subPath) (Name.fromIndex Index.first)
Name.Prod _ _ ->
@ -1031,8 +1031,13 @@ toDebugMetadata mode interfaces msgType =
Name.Prod _ _ ->
JS.Int 0
Name.Dev _ ->
JS.Json $ Encode.object $
[ ("versions", Encode.object [ ("elm", Pkg.encodeVersion Version.version) ])
, ("types", Type.encodeMetadata (Extract.fromMsg interfaces msgType))
]
Name.Dev _ debugger ->
case debugger of
Name.DebuggerOff ->
JS.Int 0
Name.DebuggerOn ->
JS.Json $ Encode.object $
[ ("versions", Encode.object [ ("elm", Pkg.encodeVersion Version.version) ])
, ("types", Type.encodeMetadata (Extract.fromMsg interfaces msgType))
]

View File

@ -4,6 +4,7 @@ module Generate.JavaScript.Name
( Name
, Mode(..)
, Target(..)
, Debugger(..)
, isServer
, toBuilder
, fromIndex
@ -53,13 +54,18 @@ newtype Name =
data Mode
= Dev Target
= Dev Target Debugger
| Prod Target ShortFieldNames
data Target = Client | Server
data Debugger
= DebuggerOn
| DebuggerOff
type ShortFieldNames =
Map.Map N.Name Name
@ -67,7 +73,7 @@ type ShortFieldNames =
isServer :: Mode -> Bool
isServer mode =
case mode of
Dev target -> isServerHelp target
Dev target _ -> isServerHelp target
Prod target _ -> isServerHelp target
@ -124,7 +130,7 @@ fromKernel home name =
fromField :: Mode -> N.Name -> Name
fromField mode name =
case mode of
Dev _ ->
Dev _ _ ->
Name (N.toBuilder name)
Prod _ fields ->

View File

@ -117,6 +117,7 @@ Executable elm
Reporting.Exit.Diff,
Reporting.Exit.Help,
Reporting.Exit.Http,
Reporting.Exit.Make,
Reporting.Exit.Publish,
Reporting.Progress,
Reporting.Progress.Bar,

View File

@ -173,6 +173,7 @@ make =
makeFlags =
flags Make.Flags
|-- onOff "debug" "Turn on the time-travelling debugger. It allows you to rewind and replay events. The events can be imported/exported into a file, which makes for very precise bug reports!"
|-- onOff "optimize" "Turn on optimizations to make code smaller and faster. For example, the compiler renames record fields to be as short as possible and unboxes values to reduce allocation."
|-- flag "output" Output.output "Specify the name of the resulting JS file. For example --output=assets/elm.js to generate the JS at assets/elm.js or --output=/dev/null to generate no output at all!"
|-- flag "report" Make.reportType "You can say --report=json to get error messages as JSON. This is only really useful if you are an editor plugin. Humans should avoid it!"

View File

@ -14,7 +14,10 @@ import qualified System.FilePath as FP
import qualified Elm.Compiler.Objects as Obj
import qualified Elm.Project as Project
import qualified Generate.Output as Output
import qualified Reporting.Exit as Exit
import qualified Reporting.Exit.Make as E
import qualified Reporting.Task as Task
import qualified Reporting.Progress as Progress
import qualified Reporting.Progress.Json as Json
import qualified Reporting.Progress.Terminal as Terminal
import Terminal.Args (Parser(..), suggestFiles)
@ -26,7 +29,8 @@ import Terminal.Args (Parser(..), suggestFiles)
data Flags =
Flags
{ _optimize :: Bool
{ _debug :: Bool
, _optimize :: Bool
, _output :: Maybe Output.Output
, _report :: Maybe ReportType
, _docs :: Maybe FilePath
@ -34,23 +38,29 @@ data Flags =
run :: [FilePath] -> Flags -> IO ()
run paths (Flags optimize output report docs) =
let
mode =
if optimize then Obj.Prod else Obj.Dev
outputOptions =
Output.Options mode Obj.Client output
makeReporter =
case report of
Nothing -> Terminal.create
Just Json -> return Json.reporter
in
do reporter <- makeReporter
run paths (Flags debug optimize output report docs) =
do reporter <- toReporter report
void $ Task.run reporter $
do summary <- Project.getRoot
Project.compile outputOptions docs summary paths
do mode <- toMode debug optimize
summary <- Project.getRoot
let options = Output.Options mode Obj.Client output
Project.compile options docs summary paths
toMode :: Bool -> Bool -> Task.Task Obj.Mode
toMode debug optimize =
case (debug, optimize) of
(True , True ) -> Task.throw $ Exit.Make E.CannotOptimizeAndDebug
(False, True ) -> return Obj.Prod
(False, False) -> return Obj.Dev
(True , False) -> return Obj.Debug
toReporter :: Maybe ReportType -> IO Progress.Reporter
toReporter report =
case report of
Nothing -> Terminal.create
Just Json -> return Json.reporter