module Development.Duplo.Scripts where
import Control.Applicative ((<*>), (<$>))
import Control.Exception (throw, SomeException(..))
import Control.Lens hiding (Action)
import Control.Monad (filterM)
import Control.Monad.Trans.Class (lift)
import Data.Function (on)
import Data.List (intercalate, nubBy)
import Data.Text.Format (left)
import Data.Text.Lazy (Text, pack, unpack, replace, splitOn)
import Data.Text.Lazy.Builder (toLazyText)
import Development.Duplo.Component (extractCompVersions)
import Development.Duplo.Files (File(..), pseudoFile)
import Development.Duplo.JavaScript.Order (order)
import Development.Duplo.Types.JavaScript
import Development.Duplo.Utilities (logStatus, headerPrintSetter, expandPaths, compile, createIntermediaryDirectories, CompiledContent, expandDeps)
import Development.Shake
import Development.Shake.FilePath ((</>))
import Language.JavaScript.Parser.SrcLocation (TokenPosn(..))
import Text.Regex (mkRegex, matchRegex)
import qualified Development.Duplo.Types.Config as TC
import qualified Language.JavaScript.Parser as JS
errorDisplayRange :: Int
errorDisplayRange = 20
build :: TC.BuildConfig
-> FilePath
-> CompiledContent ()
build config out = do
liftIO $ logStatus headerPrintSetter "Building scripts"
let cwd = config ^. TC.cwd
let util = config ^. TC.utilPath
let env = config ^. TC.env
let buildMode = config ^. TC.buildMode
let input = config ^. TC.input
let devPath = config ^. TC.devPath
let depsPath = config ^. TC.depsPath
let devCodePath = devPath </> "modules/index.js"
let depIds = config ^. TC.dependencies
let inDev = TC.isInDev config
let inTest = TC.isInTest config
lift $ createIntermediaryDirectories devCodePath
let staticPaths = case buildMode of
"development" -> [ "dev/index" ]
"test" -> [ "test/index" ]
_ -> []
++ [ "app/index" ]
let depsToExpand id = [ "components/" ++ id ++ "/app/modules" ]
let dynamicPaths = case buildMode of
"development" -> [ "dev/modules" ]
"test" -> [ "test/modules" ]
_ -> []
++ [ "app/modules" ]
++ expandDeps depIds depsToExpand
paths <- lift $ expandPaths cwd ".js" staticPaths dynamicPaths
let duploIn = if not (null input) then input else ""
compVers <- liftIO $ extractCompVersions cwd
let envVars = "var DUPLO_ENV = '" ++ env ++ "';\n"
++ "var DUPLO_IN = JSON.parse(window.atob('" ++ duploIn ++ "') || '{}' );\n"
++ "var DUPLO_VERSIONS = " ++ compVers ++ ";\n"
let compiler = (util </>) $ if inDev || inTest
then "scripts-dev.sh"
else "scripts-optimize.sh"
let pre = return . (:) (pseudoFile { _fileContent = envVars })
let prepareJs = JS.renderToString . order
let post content = return
$ either (handleParseError content) prepareJs
$ JS.parse content ""
compiled <- compile config compiler [] paths pre post
lift $ writeFileChanged out compiled
handleParseError :: String -> String -> String
handleParseError content e = exception
where
linedContent = fmap unpack $ splitOn "\n" $ pack content
lineCount = length linedContent
lineNum = readParseError e
lineRange = take errorDisplayRange
$ iterate (+ 1)
$ lineNum errorDisplayRange `div` 2
showBadLine' = showBadLine linedContent lineNum
keepInRange = max 0 . min lineCount
badLines = fmap (showBadLine' . keepInRange) lineRange
dedupe = nubBy ((==) `on` fst)
badLinesDeduped = map snd $ dedupe badLines
exception = throw
ShakeException { shakeExceptionTarget = ""
, shakeExceptionStack = []
, shakeExceptionInner = SomeException
$ ParseException
badLinesDeduped
}
showBadLine :: [String] -> LineNumber -> LineNumber -> (LineNumber, String)
showBadLine allLines badLineNum lineNum = (lineNum, line')
where
line = allLines !! lineNum
toString = unpack . toLazyText
lineNum' = toString $ left 4 ' ' $ lineNum + 1
marker = if lineNum == badLineNum
then ">> " ++ lineNum'
else " " ++ lineNum'
line' = marker ++ " | " ++ line
readParseError :: String -> LineNumber
readParseError e =
case match of
Just m -> (read $ head m) :: Int
Nothing -> throw $ InternalParserException e
where
regex = mkRegex "TokenPn [0-9]+ ([0-9]+) [0-9]+"
match = matchRegex regex e