Skip to content
Open
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
21 changes: 19 additions & 2 deletions apps/engine/deps.nix
Original file line number Diff line number Diff line change
Expand Up @@ -145,6 +145,23 @@ let
with self;
{

briefly =
let
version = "0.5.1";
drv = buildMix {
inherit version;
name = "briefly";
appConfigPath = ./config;

src = fetchHex {
inherit version;
pkg = "briefly";
sha256 = "bd684aa92ad8b7b4e0d92c31200993c4bc1469fc68cd6d5f15144041bd15cb57";
};
};
in
drv;

elixir_sense =
let
version = "e3ddc403554050221a2fd19a10a896fa7525bc02";
Expand All @@ -165,7 +182,7 @@ let

gen_lsp =
let
version = "0.11.1";
version = "0.11.2";
drv = buildMix {
inherit version;
name = "gen_lsp";
Expand All @@ -174,7 +191,7 @@ let
src = fetchHex {
inherit version;
pkg = "gen_lsp";
sha256 = "78cd7994c0e46399c71e727fe29cfb8ff41e32711c1a30ad4b92203ee0d7920d";
sha256 = "7a5ccf2403d368a82ffa968ec3993f30d41f4bc2837c69c068ed08c598340a4d";
};

beamDeps = [
Expand Down
1 change: 1 addition & 0 deletions apps/engine/mix.lock
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
%{
"benchee": {:hex, :benchee, "1.3.1", "c786e6a76321121a44229dde3988fc772bca73ea75170a73fd5f4ddf1af95ccf", [:mix], [{:deep_merge, "~> 1.0", [hex: :deep_merge, repo: "hexpm", optional: false]}, {:statistex, "~> 1.0", [hex: :statistex, repo: "hexpm", optional: false]}, {:table, "~> 0.1.0", [hex: :table, repo: "hexpm", optional: true]}], "hexpm", "76224c58ea1d0391c8309a8ecbfe27d71062878f59bd41a390266bf4ac1cc56d"},
"briefly": {:hex, :briefly, "0.5.1", "ee10d48da7f79ed2aebdc3e536d5f9a0c3e36ff76c0ad0d4254653a152b13a8a", [:mix], [], "hexpm", "bd684aa92ad8b7b4e0d92c31200993c4bc1469fc68cd6d5f15144041bd15cb57"},
"bunt": {:hex, :bunt, "1.0.0", "081c2c665f086849e6d57900292b3a161727ab40431219529f13c4ddcf3e7a44", [:mix], [], "hexpm", "dc5f86aa08a5f6fa6b8096f0735c4e76d54ae5c9fa2c143e5a1fc7c1cd9bb6b5"},
"castore": {:hex, :castore, "1.0.12", "053f0e32700cbec356280c0e835df425a3be4bc1e0627b714330ad9d0f05497f", [:mix], [], "hexpm", "3dca286b2186055ba0c9449b4e95b97bf1b57b47c1f2644555879e659960c224"},
"credo": {:hex, :credo, "1.7.12", "9e3c20463de4b5f3f23721527fcaf16722ec815e70ff6c60b86412c695d426c1", [:mix], [{:bunt, "~> 0.2.1 or ~> 1.0", [hex: :bunt, repo: "hexpm", optional: false]}, {:file_system, "~> 0.2 or ~> 1.0", [hex: :file_system, repo: "hexpm", optional: false]}, {:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}], "hexpm", "8493d45c656c5427d9c729235b99d498bd133421f3e0a683e5c1b561471291e5"},
Expand Down
21 changes: 19 additions & 2 deletions apps/expert/deps.nix
Original file line number Diff line number Diff line change
Expand Up @@ -145,6 +145,23 @@ let
with self;
{

briefly =
let
version = "0.5.1";
drv = buildMix {
inherit version;
name = "briefly";
appConfigPath = ./config;

src = fetchHex {
inherit version;
pkg = "briefly";
sha256 = "bd684aa92ad8b7b4e0d92c31200993c4bc1469fc68cd6d5f15144041bd15cb57";
};
};
in
drv;

burrito =
let
version = "1.5.0";
Expand Down Expand Up @@ -195,7 +212,7 @@ let

gen_lsp =
let
version = "0.11.1";
version = "0.11.2";
drv = buildMix {
inherit version;
name = "gen_lsp";
Expand All @@ -204,7 +221,7 @@ let
src = fetchHex {
inherit version;
pkg = "gen_lsp";
sha256 = "78cd7994c0e46399c71e727fe29cfb8ff41e32711c1a30ad4b92203ee0d7920d";
sha256 = "7a5ccf2403d368a82ffa968ec3993f30d41f4bc2837c69c068ed08c598340a4d";
};

beamDeps = [
Expand Down
1 change: 1 addition & 0 deletions apps/expert/lib/expert/engine_node.ex
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,7 @@ defmodule Expert.EngineNode do

{:error, reason} ->
IO.puts("error starting node: #{inspect(reason)}")
IO.puts("error starting node:\n #{inspect(reason)}")
end
end

Expand Down
3 changes: 2 additions & 1 deletion apps/expert/lib/expert/release.ex
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
defmodule Expert.Release do
def assemble(release) do
Mix.Task.run(:namespace, [release.path])
# In-place namespacing: both source and output are the same path
Mix.Task.run(:namespace, [release.path, release.path])

expert_root = Path.expand("../../../..", __DIR__)
engine_path = Path.join([expert_root, "apps", "engine"])
Expand Down
1 change: 1 addition & 0 deletions apps/expert/mix.lock
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
%{
"briefly": {:hex, :briefly, "0.5.1", "ee10d48da7f79ed2aebdc3e536d5f9a0c3e36ff76c0ad0d4254653a152b13a8a", [:mix], [], "hexpm", "bd684aa92ad8b7b4e0d92c31200993c4bc1469fc68cd6d5f15144041bd15cb57"},
"bunt": {:hex, :bunt, "1.0.0", "081c2c665f086849e6d57900292b3a161727ab40431219529f13c4ddcf3e7a44", [:mix], [], "hexpm", "dc5f86aa08a5f6fa6b8096f0735c4e76d54ae5c9fa2c143e5a1fc7c1cd9bb6b5"},
"burrito": {:hex, :burrito, "1.5.0", "d68ec01df2871f1d5bc603b883a78546c75761ac73c1bec1b7ae2cc74790fcd1", [:mix], [{:jason, "~> 1.4", [hex: :jason, repo: "hexpm", optional: false]}, {:req, ">= 0.5.0", [hex: :req, repo: "hexpm", optional: false]}, {:typed_struct, "~> 0.2.0 or ~> 0.3.0", [hex: :typed_struct, repo: "hexpm", optional: false]}], "hexpm", "3861abda7bffa733862b48da3e03df0b4cd41abf6fd24b91745f5c16d971e5fa"},
"credo": {:hex, :credo, "1.7.12", "9e3c20463de4b5f3f23721527fcaf16722ec815e70ff6c60b86412c695d426c1", [:mix], [{:bunt, "~> 0.2.1 or ~> 1.0", [hex: :bunt, repo: "hexpm", optional: false]}, {:file_system, "~> 0.2 or ~> 1.0", [hex: :file_system, repo: "hexpm", optional: false]}, {:jason, "~> 1.0", [hex: :jason, repo: "hexpm", optional: false]}], "hexpm", "8493d45c656c5427d9c729235b99d498bd133421f3e0a683e5c1b561471291e5"},
Expand Down
5 changes: 1 addition & 4 deletions apps/expert/priv/build_engine.exs
Original file line number Diff line number Diff line change
Expand Up @@ -31,9 +31,6 @@ install_path = Mix.install_project_dir()
dev_build_path = Path.join([install_path, "_build", "dev"])
ns_build_path = Path.join([install_path, "_build", "dev_ns"])

File.rm_rf!(ns_build_path)
File.cp_r!(dev_build_path, ns_build_path)

Mix.Task.run("namespace", [ns_build_path, "--cwd", install_path])
Mix.Task.run("namespace", [dev_build_path, ns_build_path, "--cwd", install_path, "--no-progress"])

IO.puts("engine_path:" <> ns_build_path)
21 changes: 19 additions & 2 deletions apps/forge/deps.nix
Original file line number Diff line number Diff line change
Expand Up @@ -145,9 +145,26 @@ let
with self;
{

briefly =
let
version = "0.5.1";
drv = buildMix {
inherit version;
name = "briefly";
appConfigPath = ./config;

src = fetchHex {
inherit version;
pkg = "briefly";
sha256 = "bd684aa92ad8b7b4e0d92c31200993c4bc1469fc68cd6d5f15144041bd15cb57";
};
};
in
drv;

gen_lsp =
let
version = "0.11.1";
version = "0.11.2";
drv = buildMix {
inherit version;
name = "gen_lsp";
Expand All @@ -156,7 +173,7 @@ let
src = fetchHex {
inherit version;
pkg = "gen_lsp";
sha256 = "78cd7994c0e46399c71e727fe29cfb8ff41e32711c1a30ad4b92203ee0d7920d";
sha256 = "7a5ccf2403d368a82ffa968ec3993f30d41f4bc2837c69c068ed08c598340a4d";
};

beamDeps = [
Expand Down
132 changes: 132 additions & 0 deletions apps/forge/lib/forge/namespace/file_sync.ex
Original file line number Diff line number Diff line change
@@ -0,0 +1,132 @@
defmodule Forge.Namespace.FileSync do
defmodule Classification do
defstruct changed: [],
new: [],
deleted: []
end

alias __MODULE__.Classification

@type classification :: %Classification{
changed: list({String.t(), String.t()}),
new: list({String.t(), String.t()}),
deleted: list(String.t())
}

@doc """
Classifies files into changed, new, and deleted categories.

It looks at files in both the base directory and output directory,
applying namespacing to the file names in the output directory.

Then compares the mtimes of the files to determine their classification.

If files in output_directory are not present in base_directory, they are classified as deleted.
"""
def classify_files(same, same),
do: %Classification{
changed: [],
new: [],
deleted: []
}

def classify_files(base_directory, output_directory) do
base_files = find_files(Path.join(base_directory, "lib"))
output_files = find_files(Path.join(output_directory, "lib"))

base_map =
Enum.reduce(base_files, %{}, fn base_file, acc ->
relative_path = Path.relative_to(base_file, base_directory)

namespaced_relative_path =
relative_path
|> Forge.Namespace.Path.apply()
|> maybe_namespace_filename()

dest_path = Path.join(output_directory, namespaced_relative_path)
Map.put(acc, base_file, dest_path)
end)

expected_dest_files = base_map |> Map.values() |> MapSet.new()
output_set = MapSet.new(output_files)

classification =
Enum.reduce(base_map, %Classification{}, fn {base_file, dest_path}, acc ->
if File.exists?(dest_path) do
base_mtime = File.stat!(base_file).mtime
output_mtime = File.stat!(dest_path).mtime

if base_mtime > output_mtime do
%{acc | changed: [{base_file, dest_path} | acc.changed]}
else
acc
end
else
%{acc | new: [{base_file, dest_path} | acc.new]}
end
end)

deleted_files =
output_set
|> MapSet.difference(MapSet.new(expected_dest_files))
|> MapSet.to_list()

%{classification | deleted: deleted_files}
end

@doc """
Copy new and changed files into a destination root (e.g., tmp dir) while
preserving relative paths and namespacing.
"""
def copy_new_and_changed(%Classification{} = classification, base_directory, destination_root) do
Enum.each(classification.new ++ classification.changed, fn {src, _dest} ->
relative_path = Path.relative_to(src, base_directory)
destination_path = Path.join(destination_root, relative_path)

File.mkdir_p!(Path.dirname(destination_path))
File.cp!(src, destination_path)
end)

:ok
end

@doc """
Delete files listed in the classification from the given root.
"""
def delete_removed(%Classification{} = classification) do
Enum.each(classification.deleted, fn dest ->
if File.exists?(dest) do
File.rm!(dest)
end
end)

:ok
end

defp find_files(directory) do
[directory, "**", "*"]
|> Path.join()
|> Path.wildcard()
|> Enum.filter(&File.regular?/1)
end

defp maybe_namespace_filename(file_path) do
# namespace filename for .beam and .app files
extname = Path.extname(file_path)

if extname in [".beam", ".app"] do
dirname = Path.dirname(file_path)
basename = Path.basename(file_path, extname)

namespaced_basename =
basename
|> String.to_atom()
|> Forge.Namespace.Module.apply()
|> Atom.to_string()

Path.join(dirname, namespaced_basename <> extname)
else
file_path
end
end
end
26 changes: 17 additions & 9 deletions apps/forge/lib/forge/namespace/transform/beams.ex
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ defmodule Forge.Namespace.Transform.Beams do
alias Forge.Namespace.Abstract
alias Forge.Namespace.Code

def apply_to_all(base_directory) do
def apply_to_all(base_directory, opts) do
Mix.Shell.IO.info("Rewriting .beam files")
consolidated_beams = find_consolidated_beams(base_directory)
app_beams = find_app_beams(base_directory)
Expand All @@ -29,7 +29,7 @@ defmodule Forge.Namespace.Transform.Beams do
|> Stream.run()
end)

block_until_done(0, total_files)
block_until_done(0, total_files, opts)
end

def apply(path) do
Expand All @@ -46,21 +46,29 @@ defmodule Forge.Namespace.Transform.Beams do
defp changed?(same, same), do: false
defp changed?(_, _), do: true

defp block_until_done(same, same) do
Mix.Shell.IO.info("\n done")
defp block_until_done(same, same, opts) do
if !opts[:no_progress] do
IO.write("\n")
end

Mix.Shell.IO.info("Finished namespacing .beam files")
end

defp block_until_done(current, max) do
defp block_until_done(current, max, opts) do
receive do
:progress -> :ok
end

current = current + 1
IO.write("\r")
percent_complete = format_percent(current, max)

IO.write(" Applying namespace: #{percent_complete} complete")
block_until_done(current, max)
if !opts[:no_progress] do
IO.write("\r")
percent_complete = format_percent(current, max)

IO.write(" Applying namespace: #{percent_complete} complete")
end

block_until_done(current, max, opts)
end

defp apply_and_update_progress(beam_file, caller) do
Expand Down
1 change: 1 addition & 0 deletions apps/forge/lib/forge/namespace/transform/configs.ex
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ defmodule Forge.Namespace.Transform.Configs do
base_directory
|> Path.join("**/runtime.exs")
|> Path.wildcard()
|> Enum.filter(&File.regular?/1)
|> Enum.map(&Path.absname/1)
|> tap(fn paths ->
Mix.Shell.IO.info("Rewriting #{length(paths)} config scripts.")
Expand Down
25 changes: 25 additions & 0 deletions apps/forge/lib/mix/tasks/classify.ex
Original file line number Diff line number Diff line change
@@ -0,0 +1,25 @@
defmodule Mix.Tasks.Classify do
use Mix.Task

def run([base_directory, output_directory]) do
classified_files = Forge.Namespace.FileSync.classify_files(base_directory, output_directory)

Mix.Shell.IO.info("Changed files:")

Enum.each(classified_files.changed, fn {base, output} ->
Mix.Shell.IO.info(" Changed: #{base} -> #{output}")
end)

Mix.Shell.IO.info("New files:")

Enum.each(classified_files.new, fn {base, output} ->
Mix.Shell.IO.info(" New: #{base} -> #{output}")
end)

Mix.Shell.IO.info("Deleted files:")

Enum.each(classified_files.deleted, fn output ->
Mix.Shell.IO.info(" Deleted: #{output}")
end)
end
end
Loading
Loading