Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ cabal.sandbox.config
.DS_Store
*~
travis.log

.idea


# @LAMDERA
Expand Down
6 changes: 4 additions & 2 deletions compiler/src/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ import qualified CanSer.CanSer as ToSource
import qualified Data.Text as T
import qualified Data.Utf8
import qualified Lamdera.UiSourceMap
import qualified Lamdera.Nitpick.DebugLog

-- import StandaloneInstances

Expand Down Expand Up @@ -92,16 +93,17 @@ compile pkg ifaces modul = do
annotations <- typeCheck modul_ canonical2
-- () <- debugPassText "starting nitpick" moduleName (pure ())
() <- nitpick canonical2

() <- Lamdera.Nitpick.DebugLog.hasUselessDebugLogs canonical2
let
canonical3 :: Can.Module
canonical3 =
if Lamdera.isLive
if (Lamdera.unsafePerformIO Lamdera.isLiveMode)
then Lamdera.UiSourceMap.updateDecls (Can._name canonical2) (Can._decls canonical2)
& (\newDecls -> canonical2 { Can._decls = newDecls })
else canonical2

-- () <- debugPassText "starting optimize" moduleName (pure ())

objects <- optimize modul_ annotations canonical3
return (Artifacts canonical3 annotations objects)

Expand Down
3 changes: 3 additions & 0 deletions compiler/src/Nitpick/Debug.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,8 @@ import qualified Data.Map.Utils as Map
import qualified AST.Optimized as Opt


import qualified Lamdera.Nitpick.DebugLog


-- HAS DEBUG USES

Expand Down Expand Up @@ -36,6 +38,7 @@ nodeHasDebug node =

hasDebug :: Opt.Expr -> Bool
hasDebug expression =
Lamdera.Nitpick.DebugLog.hasDebug expression $
case expression of
Opt.Bool _ -> False
Opt.Chr _ -> False
Expand Down
21 changes: 21 additions & 0 deletions compiler/src/Reporting/Error.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,8 @@ data Error
| BadDocs Docs.Error
| BadLamderaWireIncompatible String D.Doc
| BadLamdera String D.Doc
-- @LAMDERA
| LamderaBadDebugLog (NE.List A.Region)



Expand Down Expand Up @@ -98,6 +100,25 @@ toReports source err =
BadLamdera title doc ->
NE.singleton $ Lamdera.Error.report title doc

LamderaBadDebugLog regions ->
fmap
(\region ->
Report.Report "USELESS DEBUG.LOG" region [] $
Code.toSnippet source region Nothing
(
D.reflow $
"You wrote Debug.log but you forgot to provide it with a second parameter."
,
D.stack
[
D.reflow $
"Without a second parameter Debug.log won't print anything to the browser console. Here's an example of what it should look like:"
, D.dullyellow $ D.indent 4 $ D.vcat $ [ D.reflow "_ = Debug.log \"debug label\" { someData = 123 }" ]
]
)
)
regions



-- TO DOC
Expand Down
50 changes: 33 additions & 17 deletions extra/Lamdera.hs
Original file line number Diff line number Diff line change
Expand Up @@ -38,8 +38,10 @@ module Lamdera
, isExperimental_
-- , isTypeSnapshot
, isTest
, isLive
, setLive
, isLiveMode
, setLiveMode
, isCheckMode
, setCheckMode
, Ext.Common.ostype
, Ext.Common.OSType(..)
, env
Expand Down Expand Up @@ -399,14 +401,28 @@ isTest = do
isLive_ :: MVar Bool
isLive_ = unsafePerformIO $ newMVar False

setLive :: Bool -> IO ()
setLive b = do
debug $ "⚡️ set live: " <> show b
setLiveMode :: Bool -> IO ()
setLiveMode b = do
debug $ "⚡️ set mode live: " <> show b
modifyMVar_ isLive_ (\_ -> pure b)

{-# NOINLINE isLive #-}
isLive :: Bool
isLive = unsafePerformIO $ readMVar isLive_
{-# NOINLINE isLiveMode #-}
isLiveMode :: IO Bool
isLiveMode = readMVar isLive_


{-# NOINLINE isCheck_ #-}
isCheck_ :: MVar Bool
isCheck_ = unsafePerformIO $ newMVar False

setCheckMode :: Bool -> IO ()
setCheckMode b = do
debug $ "⚡️ set mode check: " <> show b
modifyMVar_ isCheck_ (\_ -> pure $! b)

{-# NOINLINE isCheckMode #-}
isCheckMode :: IO Bool
isCheckMode = readMVar isCheck_


env =
Expand Down Expand Up @@ -524,15 +540,15 @@ hindent v =

hindent_ :: String -> IO Text
hindent_ s = do
pure $ T.pack s
-- (exit, stdout, stderr) <-
-- System.Process.readProcessWithExitCode "hindent" ["--line-length","150"] s
-- `catchError` (\err -> pure (error "no exit code on failure", s, "hindent failed"))
-- if Prelude.length stderr > 0
-- then
-- pure $ T.pack stderr
-- else
-- pure $ T.pack stdout
-- pure $ T.pack s
(exit, stdout, stderr) <-
System.Process.readProcessWithExitCode "hindent" ["--line-length","150"] s
`catchError` (\err -> pure (error "no exit code on failure", s, "hindent failed"))
if Prelude.length stderr > 0
then
pure $ T.pack stderr
else
pure $ T.pack stdout


hindentFormatValue :: Show a => a -> Text
Expand Down
4 changes: 4 additions & 0 deletions extra/Lamdera/CLI/Check.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,6 +68,8 @@ run :: () -> Lamdera.CLI.Check.Flags -> IO ()
run () flags@(Lamdera.CLI.Check.Flags destructiveMigration) = do
debug_ "Starting check..."

Lamdera.setCheckMode True

-- appNameEnvM <- Env.lookupEnv "LAMDERA_APP_NAME"

forceNotProd <- Env.lookupEnv "NOTPROD"
Expand Down Expand Up @@ -102,6 +104,8 @@ run () flags@(Lamdera.CLI.Check.Flags destructiveMigration) = do
then offlineCheck root
else onlineCheck root appName inDebug localTypes externalTypeWarnings isHoistRebuild forceVersion forceNotProd inProduction_ destructiveMigration

Lamdera.setCheckMode False


offlineCheck root = do
progressDoc $ D.stack
Expand Down
170 changes: 170 additions & 0 deletions extra/Lamdera/Nitpick/DebugLog.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,170 @@
{-# LANGUAGE OverloadedStrings #-}

module Lamdera.Nitpick.DebugLog (hasDebug, hasUselessDebugLogs) where

import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Name as Name
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import NeatInterpolation

import qualified Data.Utf8
import AST.Canonical
import Elm.Package
import qualified AST.Canonical as Can
import qualified AST.Optimized as Opt
import qualified Elm.ModuleName as Module
import qualified Reporting.Annotation
import qualified Data.ByteString.Builder as B
import qualified Reporting.Error as E
import qualified Reporting.Annotation as A
import qualified Data.NonEmptyList as NE

import Lamdera
import StandaloneInstances


hasDebug :: Opt.Expr -> Bool -> Bool
hasDebug expression original = do
-- @TODO Replace with global that activates for lamdera deploy and check
let ignoreDebugLog = unsafePerformIO $ Lamdera.isCheckMode
case expression of
Opt.VarDebug name _ _ _ | ignoreDebugLog -> name /= "log"
_ -> original


hasUselessDebugLogs :: Can.Module -> Either E.Error ()
hasUselessDebugLogs canonical =
case checkDecls (Can._decls canonical) of
first : rest -> Left $ E.LamderaBadDebugLog $ NE.List first rest
[] -> Right ()

checkDecls :: Can.Decls -> [A.Region]
checkDecls decls =
case decls of
Can.Declare def nextDecl ->
checkDefs def ++ checkDecls nextDecl

Can.DeclareRec def remainingDefs nextDecl ->
checkDefs def ++ checkDecls nextDecl ++ concatMap (checkDefs) remainingDefs

Can.SaveTheEnvironment ->
[]



checkDefs :: Can.Def -> [A.Region]
checkDefs def =
case def of
Can.Def name patterns expr ->
checkExpr (Reporting.Annotation.toValue name) expr

Can.TypedDef name freeVars patterns expr type_ ->
checkExpr (Reporting.Annotation.toValue name) expr


checkExpr :: Name.Name -> Can.Expr -> [A.Region]
checkExpr functionName (Reporting.Annotation.At _ expr) =
case expr of
Can.VarLocal name ->
[]

Can.VarTopLevel canonical name ->
[]

Can.VarKernel name name2 ->
[]

Can.VarForeign canonical name annotation ->
[]

Can.VarCtor ctorOpts canonical name zeroBased annotation ->
[]

Can.VarDebug canonical name annotation ->
[]

Can.VarOperator name canonical name2 annotation ->
[]

Can.Chr string ->
[]

Can.Str string ->
[]

Can.Int int ->
[]

Can.Float float ->
[]

Can.List exprs ->
concatMap (checkExpr functionName) exprs

Can.Negate expr ->
checkExpr functionName expr

Can.Binop name canonical name2 annotation expr expr2 ->
checkExpr functionName expr ++ checkExpr functionName expr2

Can.Lambda patterns expr ->
checkExpr functionName expr

Can.Call expr exprs ->
checkExpr functionName expr ++ concatMap (checkExpr functionName) exprs

Can.If exprs expr ->
checkExpr functionName expr
++ concatMap
(\(first, second) ->
checkExpr functionName first ++ checkExpr functionName second
)
exprs

Can.Let def expr ->
checkExpr functionName expr ++ checkDefs def

Can.LetRec defs expr ->
checkExpr functionName expr ++ concatMap (checkDefs) defs

Can.LetDestruct
(Reporting.Annotation.At (A.Region start _) Can.PAnything)
(Reporting.Annotation.At (A.Region _ end) (Can.Call (Reporting.Annotation.At _ (Can.VarDebug _ "log" annotation )) [ firstParam ]))
expr ->
[ A.Region start end ] ++ checkExpr functionName expr

Can.LetDestruct pattern expr expr2 ->
checkExpr functionName expr ++ checkExpr functionName expr2

Can.Case expr caseBranches ->
checkExpr functionName expr
++ concatMap
(\(Can.CaseBranch _ caseExpr) -> checkExpr functionName caseExpr)
caseBranches

Can.Accessor name ->
[]

Can.Access expr name ->
checkExpr functionName expr

Can.Update name expr fieldUpdates ->
checkExpr functionName expr
++ concatMap (\(Can.FieldUpdate _ expr) -> checkExpr functionName expr) (Map.elems fieldUpdates)

Can.Record fields ->
concatMap (\field -> checkExpr functionName field) (Map.elems fields)

Can.Unit ->
[]

Can.Tuple expr expr2 maybeExpr ->
checkExpr functionName expr
++ checkExpr functionName expr2
++ concatMap (checkExpr functionName) maybeExpr


Can.Shader shaderSource shaderTypes ->
[]
2 changes: 1 addition & 1 deletion terminal/src/Develop.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ run () flags = do
runWithRoot :: FilePath -> Flags -> IO ()
runWithRoot root (Flags maybePort) =
do
Lamdera.setLive True
Lamdera.setLiveMode True
let port = maybe 8000 id maybePort
liftIO $ Lamdera.stdoutSetup
atomicPutStrLn $ "Go to http://localhost:" ++ show port ++ " to see your project dashboard."
Expand Down
Loading