module Hakyll.Typescript.TS
(
compressJtsCompiler,
compressJtsCompilerWith,
compressTsCompiler,
compressTsCompilerWith,
jtsCompiler,
jtsCompilerWith,
tsCompiler,
tsCompilerWith,
TSArgs
)
where
import Data.ByteString.Lazy.Char8 (ByteString)
import Hakyll.Core.Item
import Hakyll.Core.Compiler
import Hakyll.Process (execName, execCompilerWith, ExecutableArg(..), CompilerOut(CStdOut))
import Hakyll.Typescript.Internal
type TSArgs = [String]
compressJtsCompiler :: Compiler (Item ByteString)
compressJtsCompiler :: Compiler (Item ByteString)
compressJtsCompiler = TSArgs -> Compiler (Item ByteString)
compressJtsCompilerWith TSArgs
forall a. Monoid a => a
mempty
compressTsCompiler :: Compiler (Item ByteString)
compressTsCompiler :: Compiler (Item ByteString)
compressTsCompiler = TSArgs -> Compiler (Item ByteString)
compressTsCompilerWith TSArgs
forall a. Monoid a => a
mempty
compressJtsCompilerWith :: TSArgs -> Compiler (Item ByteString)
compressJtsCompilerWith :: TSArgs -> Compiler (Item ByteString)
compressJtsCompilerWith TSArgs
args = Compiler (Item ByteString) -> Compiler (Item ByteString)
withMinifyJs (Compiler (Item ByteString) -> Compiler (Item ByteString))
-> Compiler (Item ByteString) -> Compiler (Item ByteString)
forall a b. (a -> b) -> a -> b
$ TSArgs -> Compiler (Item ByteString)
jtsCompilerWith TSArgs
args
compressTsCompilerWith :: TSArgs -> Compiler (Item ByteString)
compressTsCompilerWith :: TSArgs -> Compiler (Item ByteString)
compressTsCompilerWith TSArgs
args = Compiler (Item ByteString) -> Compiler (Item ByteString)
withMinifyJs (Compiler (Item ByteString) -> Compiler (Item ByteString))
-> Compiler (Item ByteString) -> Compiler (Item ByteString)
forall a b. (a -> b) -> a -> b
$ TSArgs -> Compiler (Item ByteString)
tsCompilerWith TSArgs
args
jtsCompiler :: Compiler (Item ByteString)
jtsCompiler :: Compiler (Item ByteString)
jtsCompiler = TSArgs -> Compiler (Item ByteString)
jtsCompilerWith TSArgs
forall a. Monoid a => a
mempty
tsCompiler :: Compiler (Item ByteString)
tsCompiler :: Compiler (Item ByteString)
tsCompiler = TSArgs -> Compiler (Item ByteString)
tsCompilerWith TSArgs
forall a. Monoid a => a
mempty
jtsCompilerWith :: TSArgs -> Compiler (Item ByteString)
jtsCompilerWith :: TSArgs -> Compiler (Item ByteString)
jtsCompilerWith TSArgs
args = TSArgs -> Compiler (Item ByteString)
tsCompilerWith (TSArgs -> Compiler (Item ByteString))
-> TSArgs -> Compiler (Item ByteString)
forall a b. (a -> b) -> a -> b
$ [[Char]
"--allowJs", [Char]
"true"] TSArgs -> TSArgs -> TSArgs
forall a. Semigroup a => a -> a -> a
<> TSArgs
args
tsCompilerWith :: TSArgs -> Compiler (Item ByteString)
tsCompilerWith :: TSArgs -> Compiler (Item ByteString)
tsCompilerWith TSArgs
args = ExecutableName
-> ExecutableArgs -> CompilerOut -> Compiler (Item ByteString)
execCompilerWith ([Char] -> ExecutableName
execName [Char]
"tsc") ExecutableArgs
allArgs CompilerOut
CStdOut
where
defaultArgs :: ExecutableArgs
defaultArgs = [[Char] -> ExecutableArg
ProcArg [Char]
"--outFile", [Char] -> ExecutableArg
ProcArg [Char]
"/dev/stdout"]
allArgs :: ExecutableArgs
allArgs = ExecutableArgs
defaultArgs ExecutableArgs -> ExecutableArgs -> ExecutableArgs
forall a. Semigroup a => a -> a -> a
<> ([Char] -> ExecutableArg) -> TSArgs -> ExecutableArgs
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Char] -> ExecutableArg
ProcArg TSArgs
args ExecutableArgs -> ExecutableArgs -> ExecutableArgs
forall a. Semigroup a => a -> a -> a
<> [ExecutableArg
HakFilePath]