Skip to main content
Glama
shell_buck2_utils.erl5.33 kB
%% Copyright (c) Meta Platforms, Inc. and affiliates. %% %% This source code is licensed under both the MIT license found in the %% LICENSE-MIT file in the root directory of this source tree and the Apache %% License, Version 2.0 found in the LICENSE-APACHE file in the root directory %% of this source tree. %% @format -module(shell_buck2_utils). -compile(warn_missing_spec_all). -moduledoc """ Documentation for shell_buck2_utils, ways to use it, ways to break it, etc. etc """. -eqwalizer(ignore). %% Public API -export([ project_root/0, cell_root/0, rebuild_modules/1, buck2_build_targets/1, buck2_query/1, buck2_query/2, buck2_query/3, run_command/2, run_command/3, get_additional_paths/1 ]). -type opt() :: {at_root, boolean()} | {replay, boolean()}. -spec project_root() -> file:filename(). project_root() -> root(project). -spec cell_root() -> file:filename(). cell_root() -> root(cell). -spec root(Type :: cell | project) -> file:filename(). root(Type) -> case run_command("buck2 root --kind=~s 2>/dev/null", [Type], [{at_root, false}, {replay, false}]) of {ok, Output} -> Dir = string:trim(Output), case filelib:is_dir(Dir) of true -> Dir; false -> error({project_root_not_found, Dir}) end; error -> error(failed_to_query_project_root) end. -spec rebuild_modules([module()]) -> ok | error. rebuild_modules([]) -> ok; rebuild_modules(Modules) -> case lists:filter(fun(Module) -> code:which(Module) == non_existing end, Modules) of [] -> ok; Missing -> error({non_existing, Missing}) end, RelSources = [proplists:get_value(source, Module:module_info(compile)) || Module <- Modules], {ok, RawQueryResult} = buck2_query("owner(\%s)", RelSources), Targets = string:split(string:trim(RawQueryResult), "\n", all), case Targets of [[]] -> io:format("ERROR: couldn't find targets for ~w~n", [Modules]), error; _ -> buck2_build_targets(Targets) end. -spec buck2_build_targets([string() | binary()]) -> ok | error. buck2_build_targets(Targets) -> case run_command("buck2 build --reuse-current-config --console super ~s", [ lists:join(" ", Targets) ]) of {ok, _Output} -> ok; error -> error end. -spec buck2_query(string()) -> {ok, binary()} | error. buck2_query(Query) -> buck2_query(Query, []). -spec buck2_query(string(), [string()]) -> {ok, binary()} | error. buck2_query(Query, Args) -> buck2_query(Query, "", Args). -spec buck2_query(string(), string(), [string()]) -> {ok, binary()} | error. buck2_query(Query, BuckArgs, Args) -> run_command("buck2 uquery ~s --reuse-current-config \"~s\" ~s 2> /dev/null", [ BuckArgs, Query, lists:join(" ", Args) ]). -spec run_command(string(), [term()]) -> {ok, binary()} | error. run_command(Fmt, Args) -> run_command(Fmt, Args, []). -spec run_command(string(), [term()], [opt()]) -> {ok, binary()} | error. run_command(Fmt, Args, Options) -> PortOpts0 = [exit_status, stderr_to_stdout], PortOpts1 = case proplists:get_value(at_root, Options, true) of true -> Root = project_root(), [{cd, Root} | PortOpts0]; false -> PortOpts0 end, RawCmd = io_lib:format(Fmt, Args), Cmd = unicode:characters_to_list(RawCmd), Replay = proplists:get_value(replay, Options, true), Port = erlang:open_port({spawn, Cmd}, PortOpts1), port_loop(Port, Replay, []). -spec port_loop(port(), boolean(), [binary()]) -> {ok, binary()} | error. port_loop(Port, Replay, StdOut) -> receive {Port, {exit_status, 0}} -> {ok, unicode:characters_to_binary(lists:reverse(StdOut))}; {Port, {exit_status, _}} -> error; {Port, {data, Data}} -> case Replay of true -> io:put_chars(Data); false -> ok end, port_loop(Port, Replay, [Data | StdOut]) end. -spec get_additional_paths(file:filename_all()) -> [file:filename_all()]. get_additional_paths(Path) -> case run_command( "buck2 bxl --reuse-current-config --console super prelude//erlang/shell/shell.bxl:ebin_paths -- --source ~s", [Path] ) of {ok, Output} -> MaybeOutputPaths = [ filter_escape_chars(OutputPath) || OutputPath <- string:split(Output, "\n", all) ], MaybeAllPaths = lists:concat([ [OutputPath, filename:join(OutputPath, "ebin")] || OutputPath <- MaybeOutputPaths, filelib:is_dir(OutputPath) ]), [MaybePath || MaybePath <- MaybeAllPaths, filelib:is_dir(MaybePath)]; error -> [] end. %% copied from stackoverflow: https://stackoverflow.com/questions/14693701/how-can-i-remove-the-ansi-escape-sequences-from-a-string-in-python -define(ANSI_ESCAPE_REGEX, "(\x9B|\x1B\\[)[0-?]*[ -/]*[@-~]" ). -spec filter_escape_chars(String :: string()) -> string(). filter_escape_chars(String) -> lists:flatten(io_lib:format("~s", [re:replace(String, ?ANSI_ESCAPE_REGEX, "", [global])])).

Latest Blog Posts

MCP directory API

We provide all the information about MCP servers via our MCP API.

curl -X GET 'https://glama.ai/api/mcp/v1/servers/systeminit/si'

If you have feedback or need assistance with the MCP directory API, please join our Discord server