{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE NoImplicitPrelude #-} -- | A general purpose build tool. -- -- - with a nix build, results are linked in _/bild/nix/ -- - for a dev build, results are stored in _/bild/dev/ module Biz.Bild where import Alpha hiding ((<.>), sym) import qualified Data.Char as Char import qualified Data.List as List import qualified Data.Text as Text import qualified System.Directory as Dir import qualified System.Environment as Env import qualified System.Exit as Exit import System.FilePath ((<.>), ()) import qualified System.Process as Process import Text.Regex.Applicative import qualified Prelude main :: IO () main = Env.getArgs /> head >>= \case Nothing -> Exit.die "usage: bild " Just target -> analyze target >>= build type Namespace = String type Dep = String type Exe = String data Compiler = Ghc | Ghcjs | Nix deriving (Show) data Target = Target { -- | Output executable name exe :: Exe, -- | Fully qualified namespace partitioned by '.' namespace :: Namespace, -- | Absolute path to file path :: FilePath, -- | Parsed/detected dependencies deps :: [Dep], -- | Which compiler should we use? compiler :: Compiler } deriving (Show) analyze :: String -> IO Target analyze s = do root <- Env.getEnv "BIZ_ROOT" cwd <- Dir.getCurrentDirectory -- this is a hack to support multiple file types. Ideally we would just detect -- which file extensions exist let path = cwd reps "." "/" s |> reps "/hs" ".hs" |> reps "/nix" ".nix" content <- lines match metaExe |> catMaybes |> head |> require "exe" return Target { namespace = require "namespace" <| path |> reps root "" |> reps ".hs" "" |> reps ".nix" "" |> reps "/" "." |> List.stripPrefix "." >>= match metaNamespace, deps = content /> match metaDep |> catMaybes, compiler = if ".hs" `List.isSuffixOf` path then if ".js" `List.isSuffixOf` exe then Ghcjs else Ghc else Nix, .. } build :: Target -> IO () build Target {..} = do root <- Env.getEnv "BIZ_ROOT" case compiler of Ghc -> do putText <| "bild: ghc: " <> Text.pack namespace let out = root "_/bild/dev/bin" Dir.createDirectoryIfMissing True out Process.callProcess "ghc" [ "-Werror", "-i" <> root, "-odir", root "_/bild/int", "-hidir", root "_/bild/int", "--make", path, "-main-is", namespace, "-o", out exe ] Ghcjs -> do putText <| "bild: ghcjs: " <> Text.pack namespace let out = root "_/bild/dev/static" Dir.createDirectoryIfMissing True out Process.callProcess "ghcjs" [ "-Werror", "-i" <> root, "-odir", root "_/bild/int", "-hidir", root "_/bild/int", "--make", path, "-main-is", namespace, "-o", out exe ] Nix -> do putText <| "bild: nix: " <> Text.pack namespace cwd <- Dir.getCurrentDirectory let qualifiedTarget = reps root "" cwd <> namespace Process.callProcess "nix-build" [ "-o", root "_/bild/nix" qualifiedTarget, root "default.nix", "--attr", qualifiedTarget ] metaNamespace :: RE Char Namespace metaNamespace = name <> many (sym '.') <> name where name = many (psym Char.isUpper) <> many (psym Char.isLower) metaDep :: RE Char Dep metaDep = string "-- : dep " *> many (psym Char.isAlpha) metaExe :: RE Char Exe metaExe = string "-- : exe " *> many (psym (/= ' ')) require :: Text -> Maybe a -> a require s (Just x) = x require s Nothing = panic <| s <> " not found" -- | Replace 'a' in 's' with 'b'. reps :: String -> String -> String -> String reps a b s@(x : xs) = if isPrefixOf a s then-- then, write 'b' and replace jumping 'a' substring b ++ reps a b (drop (length a) s) else-- then, write 'x' char and try to replace tail string x : reps a b xs reps _ _ [] = []