summaryrefslogtreecommitdiff
path: root/Biz
diff options
context:
space:
mode:
Diffstat (limited to 'Biz')
-rw-r--r--Biz/Bild.hs149
-rwxr-xr-xBiz/Bild.scm158
2 files changed, 131 insertions, 176 deletions
diff --git a/Biz/Bild.hs b/Biz/Bild.hs
index 983f778..ee0d78a 100644
--- a/Biz/Bild.hs
+++ b/Biz/Bild.hs
@@ -3,10 +3,122 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}
--- | A general purpose build tool.
---
--- - with a nix build, results are linked in _/bild/nix/<target>
--- - for a dev build, results are stored in _/bild/dev/<target>
+{- | A general purpose build tool.
+
+Not all of the below design is implemented. Currently:
+
+- with a nix build, results are linked in _/bild/nix/<target>
+- for a dev build, results are stored in _/bild/dev/<target>
+
+-----------------------------------------------------------------------------
+
+== Design constraints
+
+ * only input is a namespace, no subcommands, no packages
+
+ * no need to write specific build rules
+
+ * one rule for hs, one for rs, one for scm, and so on
+
+ * no need to distinguish between exe and lib, just have a single output
+
+ * never concerned with deployment/packaging - leave that to another tool
+ (scp? tar?)
+
+== Features
+
+ * namespace maps to filesystem
+
+ * no need for `bild -l` for listing available targets. Use `ls` or `tree`
+
+ * you build namespaces, not files/modules/packages/etc
+
+ * namespace maps to language modules
+
+ * build settings can be set in the file comments
+
+ * pwd is always considered the the source directory, no `src` vs `doc` etc.
+
+ * build methods automaticatly detected with file extensions
+
+ * flags modify the way to interact with the build, some ideas:
+
+ * -s = jump into a shell and/or repl
+
+ * -p = turn on profiling
+
+ * -t = limit build by type (file extension)
+
+ * -e = exclude some regex in the ns tree
+
+ * -o = optimize level
+
+== Example Commands
+
+> bild [-spt] <target..>
+
+The general scheme is to build the things described by the targets. A target
+is a namespace. You can list as many as you want, but you must list at least
+one. It could just be `.` for the current directory. Build outputs will go
+into the _/bild directory in the root of the project.
+
+> bild a.b
+
+Or `bild a/b`. This shows building a file at ./a/b.hs, this will translate to
+something like `ghc --make A.B`.
+
+> bild -s <target>
+
+Starts a repl/shell for target.
+ - if target.hs, load ghci
+ - if target.scm, load scheme repl
+ - if target.clj, load a clojure repl
+ - if target.nix, load nix-shell
+ - and so on.
+
+> bild -p <target>
+
+build target with profiling (if available)
+
+> bild -t nix target
+
+only build target.nix, not target.hs and so on (in the case of multiple
+targets with the same name but different extension).
+
+== Build Metadata
+
+Metadata is set in the comments with a special syntax. For third-party deps,
+we list the deps in comments in the target file, like:
+
+> -- : dep aeson
+
+The output executable is named with:
+
+> -- : exe my-program
+
+or
+
+> -- : exe my-ap.js
+
+When multiple compilers are possible (e.g. ghc vs ghcjs) we chose ghcjs when
+the target exe ends in .js.
+
+This method of setting metadata in the module comments works pretty well,
+and really only needs to be done in the entrypoint module anyway.
+
+Local module deps are included by just giving the repo root to the compiler
+that bild calls out to.
+
+== Questions
+
+ * how to handle multiple output formats?
+
+ * e.g. that ghcjs and ghc take the same input files...
+
+ * say you have a .md file, you want to bild it to pdf, html, and more. What
+ do?
+
+-}
module Biz.Bild where
import Alpha hiding ((<.>), sym)
@@ -16,9 +128,9 @@ 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 System.FilePath ((</>))
import qualified System.Process as Process
-import Text.Regex.Applicative
+import qualified Text.Regex.Applicative as Regex
import qualified Prelude
main :: IO ()
@@ -55,10 +167,11 @@ 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
+ -- which file extensions exist, then return [Target], which can then be built
+ -- in parallel
let path = cwd </> reps "." "/" s |> reps "/hs" ".hs" |> reps "/nix" ".nix"
content <- lines </ Prelude.readFile path
- let exe = content /> match metaExe |> catMaybes |> head |> require "exe"
+ let exe = content /> Regex.match metaExe |> catMaybes |> head |> require "exe"
return
Target
{ namespace =
@@ -69,8 +182,8 @@ analyze s = do
|> reps ".nix" ""
|> reps "/" "."
|> List.stripPrefix "."
- >>= match metaNamespace,
- deps = content /> match metaDep |> catMaybes,
+ >>= Regex.match metaNamespace,
+ deps = content /> Regex.match metaDep |> catMaybes,
compiler =
if ".hs" `List.isSuffixOf` path
then if ".js" `List.isSuffixOf` exe then Ghcjs else Ghc
@@ -133,19 +246,19 @@ build Target {..} = do
qualifiedTarget
]
-metaNamespace :: RE Char Namespace
-metaNamespace = name <> many (sym '.') <> name
+metaNamespace :: Regex.RE Char Namespace
+metaNamespace = name <> Regex.many (Regex.sym '.') <> name
where
- name = many (psym Char.isUpper) <> many (psym Char.isLower)
+ name = Regex.many (Regex.psym Char.isUpper) <> Regex.many (Regex.psym Char.isLower)
-metaDep :: RE Char Dep
-metaDep = string "-- : dep " *> many (psym Char.isAlpha)
+metaDep :: Regex.RE Char Dep
+metaDep = Regex.string "-- : dep " *> Regex.many (Regex.psym Char.isAlpha)
-metaExe :: RE Char Exe
-metaExe = string "-- : exe " *> many (psym (/= ' '))
+metaExe :: Regex.RE Char Exe
+metaExe = Regex.string "-- : exe " *> Regex.many (Regex.psym (/= ' '))
require :: Text -> Maybe a -> a
-require s (Just x) = x
+require _ (Just x) = x
require s Nothing = panic <| s <> " not found"
-- | Replace 'a' in 's' with 'b'.
diff --git a/Biz/Bild.scm b/Biz/Bild.scm
deleted file mode 100755
index 5a769de..0000000
--- a/Biz/Bild.scm
+++ /dev/null
@@ -1,158 +0,0 @@
-;;
-;; bild - a simple build tool
-;;
-;;; Notice:
-;;
-;; This is under active development. For now this is just a convenience wrapper
-;; around `nix build`. The below commentary describes how this tool *should*
-;; work.
-;;
-;;; Commentary:
-;;
-;; Design constraints
-;;
-;; - only input is a namespace, no subcommands, no packages
-;; - no need to write specific build rules
-;; - one rule for hs, one for rs, one for scm, and so on
-;; - no need to distinguish between exe and lib, just have a single output
-;; - never concerned with deployment/packaging - leave that to another tool (scp? tar?))
-;;
-;; Features
-;;
-;; - namespace maps to filesystem
-;; - no need for `bild -l` for listing available targets. Use `ls` or `tree`
-;; - you build namespaces, not files/modules/packages/etc
-;; - namespace maps to language modules
-;; - build settings can be set in the file comments
-;; - pwd is always considered the the source directory, no `src` vs `doc` etc.
-;; - build methods automaticatly detected with file extensions
-;; - flags modify the way to interact with the build
-;; - -s = jump into a shell and/or repl
-;; - -p = turn on profiling
-;; - -t = limit build by type
-;; - -e = exclude some regex in the ns tree
-;; - -o = optimize level
-;;
-;; Example Commands
-;;
-;; bild [-rpt] <target..>
-;;
-;; The general scheme is to build the things described by the targets. A target
-;; is a namespace. You can list as many as you want, but you must list at least
-;; one. It could just be `.` for the current directory. Build outputs will go
-;; into the _/bild directory in the root of the project.
-;;
-;; bild biz.web
-;;
-;; Or `bild biz/web`. This shows building a file at ./biz/web.hs, this will
-;; translate to something like `ghc --make Biz.Web`.
-;;
-;; bild -r <target>
-;;
-;; Starts a repl/shell for target.
-;; - if target.hs, load ghci
-;; - if target.scm, load scheme repl
-;; - if target.clj, load a clojure repl
-;; - if target.nix, load nix-shell
-;; - and so on.
-;;
-;; bild -p <target>
-;;
-;; build target with profiling (if available)
-;;
-;; bild -t nix target
-;;
-;; only build target.nix, not target.hs and so on (in the case of multiple
-;; targets with the same name but different extension).
-;;
-;; Here is an example integration with GHC. Given the following command-line
-;; invocation to compile the namespace 'com.simatime.bild' which depends on
-;; 'com.simatime.lib':
-;;
-;; ghc com/simatime/bild.hs -i com/simatime/lib.hs -o _/bild -v \
-;; -main-is Biz.Bild.main
-;;
-;; The general template of which is:
-;;
-;; ghc <source> -i <deps..> -o <target> -main-is <target>.main
-;;
-;; Some definitions:
-;;
-;; - <source> is some source file
-;; - <deps..> is the stack of dependencies
-;; - <target> is the target namespace, indicated by 'bild <target>'
-;;
-;; To fill out the build template, we can parse the file for known
-;; namespaces. The general recipe is:
-;;
-;; 1. Create a list of namespaces in my git repo. This can be cached, or I can
-;; integrate with git somehow.
-;; 2. Read the <source> file corresponding to <target>
-;; 3. Look for 'import <namespace>', where <namespace> is a namespace in the
-;; aforementioned cache.
-;; 4. If found, then save current build as a continuation and compile
-;; <namespace>. Result gets put on the dependency stack
-;; 5. When finished, return to building <target>
-;;
-;; Once the build command template is filled out, we can create the nix expression.
-;;
-;; Questions
-;;
-;; - how to import (third-party) dependencies?
-;; 1 just don't have them...? yeah right
-;; 2 the target.nix could be the build description for target.hs
-;; 3 just use a default.nix for the com.whatever
-;; 4 have a deps.nix file
-;; 5 list them in the file with other settings. Starting with Haskell,
-;; have comments like `{-: PACKAGE base <5.0.0.0 :-}' or `-- : PACKAGE base <5.0.0.0'.
-;; Other languages could use `#:` for the special prefix, basically just
-;; a comment plus colon.
-;; - how to handle multiple output formats?
-;; - e.g. that ghcjs and ghc take the same input files...
-;; - say you have a .md file, you want to bild it to pdf, html, and more. What do?
-;; - i guess the nix file could return a set of drvs instead of a single drv
-;;
-;; TODO
-;; - stream output from 'nix build' subprocess
-;; - get rid of guile notes during execution
-;; - ns<->path macro
-;; - support list (scheme namespace) in ns<->path fns
-;;
-;;; Code:
-
-(define-module (Biz Bild)
- #:use-module ((ice-9 popen) #:prefix popen/)
- #:use-module ((ice-9 format) #:select (format))
- #:use-module ((ice-9 rdelim) #:prefix rdelim/)
- #:use-module ((Alpha Core) #:select (fmt))
- #:use-module ((Alpha Shell) #:prefix sh/)
- #:use-module ((Alpha String) #:prefix string/)
- #:export (ns?
- ns->path
- path->ns
- main))
-
-(define (main args)
- (let* ((root (sh/exec "git rev-parse --show-toplevel"))
- (target (cadr args))
- (path (ns->path target)))
- (display (fmt ":: bild ~a...\r" target))
- (sh/exec (fmt "nix build -f ~a/default.nix ~a"
- root target))
- (display (fmt ":: bilt ~a" target))))
-
-(define ns? symbol?)
-
-(define (ns->path ns)
- (let ((to-path (lambda (s) (string/replace-char s #\. #\/))))
- (cond
- ((symbol? ns) (to-path (symbol->string ns)))
- ((string? ns) (to-path ns))
- (else (error "ns should be a string or symbol")))))
-
-(define (path->ns path)
- (let ((to-ns (lambda (s) (string/replace-char s #\/ #\.))))
- (cond
- ((symbol? path) (to-ns (symbol->string path)))
- ((string? path) (to-ns path))
- (else (error "path should be a string or symbol")))))