SisMaker пре 4 година
комит
7c91b4e172
12 измењених фајлова са 1358 додато и 0 уклоњено
  1. +24
    -0
      .gitignore
  2. +21
    -0
      LICENSE
  3. +41
    -0
      README.md
  4. +45
    -0
      erlSync.sample.config
  5. +28
    -0
      include/erlSync.hrl
  6. +8
    -0
      rebar.config
  7. +46
    -0
      src/erlSync.app.src
  8. +61
    -0
      src/erlSync.erl
  9. +10
    -0
      src/erlSync_app.erl
  10. +27
    -0
      src/erlSync_sup.erl
  11. +691
    -0
      src/sync/esScanner.erl
  12. +356
    -0
      src/sync/esUtils.erl

+ 24
- 0
.gitignore Прегледај датотеку

@ -0,0 +1,24 @@
.eunit
*.o
*.beam
*.plt
erl_crash.dump
.concrete/DEV_MODE
# rebar 2.x
.rebar
rel/example_project
ebin/*
deps
# rebar 3
.rebar3
_build/
_checkouts/
rebar.lock
# idea
.idea
*.iml
rebar3.crashdump
*~

+ 21
- 0
LICENSE Прегледај датотеку

@ -0,0 +1,21 @@
MIT License
Copyright (c) 2020 AICells
Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in all
copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
SOFTWARE.

+ 41
- 0
README.md Прегледај датотеку

@ -0,0 +1,41 @@
# erlSync
otp21.2+
改造自 [sync](https://github.com/rustyio/sync) 有兴趣可以了解一下, 本项目仅仅在此基础做了一些封装改动和优化,工作原理并无差别
# 工作原理
启动后,Sync会收集有关已加载模块,ebin目录,源文件,编译选项等的信息。
然后,Sync会定期检查源文件的最后修改日期。如果自上次扫描以来文件已更改,则Sync会使用上一组编译选项自动重新编译模块。如果编译成功,它将加载更新的模块。否则,它将编译错误输出到控制台。
同步还会定期检查任何梁文件的上次修改日期,如果文件已更改,则会自动重新加载。
扫描过程会在运行的Erlang VM上增加1%到2%的CPU负载。已经采取了很多措施将其保持在较低水平。
但这仅适用于开发模式,请勿在生产中运行。
# 使用
启动自动编译与加载
erlSync:run().
暂停自动编译与加载
erlSync:pause().
启动或者关闭集群同步加载
erlSync:swSyncNode(TrueOrFalse).
设置编译与加载日志提示
erlSync:setLog(Val).
设置加载后的钩子函数(支持匿名函数, {Mod, Fun}(Fun函数只有一个参数)格式, 以及他们的列表组合)
erlSync:setOnsync(FunOrFuns).
# 配置说明
参见erlSync.sample.config
默认配置为
[
{erlSync,
[
{moduleTime, 30000},
{srcDirTime, 6000},
{srcFileTime, 6000},
{compareBeamTime, 4000},
{compareSrcFileTime, 4000},
{srcDirs, undefined}
{log, all},
{descendant, fix},
{onlyMods, []},
{excludedMods, []}
]
}
]

+ 45
- 0
erlSync.sample.config Прегледај датотеку

@ -0,0 +1,45 @@
[
{erlSync, [
%% 扫描module的间隔时间
{moduleTime, 40000},
%% 扫描 源码目录的间隔时间
{srcDirTime, 6000},
%% 扫描 源码文件的间隔时间
{srcFileTime, 6000},
%% 对比加载beam 文件的间隔时间
{compareBeamTime, 2000},
%% 对比编译erl hrl文件的间隔时间
{compareSrcFileTime, 2000},
%% 编译和加载以及其他一些日志的提示级别设置
%% 有效值: all | none | [success | warnings | errors]
%% 默认值: all
{log, all},
%% 这个参数用于设置特殊目录下的文件检查编译与加载
%% 格式:{srcDirs, {strategy(), [srcDirDescr()]}} | {srcDirs, undefined}
%% -type strategy() :: add | only.
%% 如果 strategy() is only, 仅仅扫描指定目录下的文件编译与加载. 如果 strategy() is add, 会扫描添加的指定目录同步编译与加载.
%% -type srcDirDescr() :: { Dir :: file:filename(), [Options :: compile_option()]}.
%% 默认值:undefined 根据当前工作目录 和 已经加载的模块做来得出需要扫描的目录
{srcDirs, {strategy(), [srcDirDescr()]}},
%% 这个参数用来设置 怎么处理 当beam文件的源文件目录不是当前工作的子目录时的情况
%% 有效值: fix | allow | ignore
%% * fix = 尝试在当前目录下查找源文件
%% * allow = 不要做任何特别的事情,使用beam源文件原始路径查找该文件
%% * ignore = 而忽略对其源路径的任何更改
%% 默认值: fix
{descendant, fix},
%% 仅仅同步编译和加载该参数指定的模块
%% default: [] 为空的时候 该参数无效
{onlyMods, []},
%% 不同步编译和加载该参数指定的模块
%% default: [] 为空的时候 该参数无效
{excludedMods, []}
]}
].

+ 28
- 0
include/erlSync.hrl Прегледај датотеку

@ -0,0 +1,28 @@
-define(LOG_ON(Val), Val == true; Val == all; Val == skip_success; is_list(Val), Val =/= []).
-define(gTimeout(Type, Time), begin
TimerRef = erlang:start_timer(Time, self(), {doSync, Type}),
case erlang:get({pdTimerRef, Type}) of
undefined ->
erlang:put({pdTimerRef, Type}, TimerRef);
OldTimerRef ->
erlang:cancel_timer(OldTimerRef),
erlang:put({pdTimerRef, Type}, TimerRef)
end
end).
-define(Log, log).
-define(moduleTime, moduleTime).
-define(srcDirTime, srcDirTime).
-define(srcFileTime, srcFileTime).
-define(compareBeamTime, compareBeamTime).
-define(compareSrcFileTime, compareSrcFileTime).
-define(srcDirs, srcDirs).
-define(onlyMods, onlyMods).
-define(excludedMods, excludedMods).
-define(descendant, descendant).
-define(CfgList, [{?Log, all}, {?moduleTime, 30000}, {?srcDirTime, 6000}, {?srcFileTime, 6000}, {?compareBeamTime, 4000}, {?compareSrcFileTime, 4000}, {?srcDirs, undefined}, {?onlyMods, []}, {?excludedMods, []}, {?descendant, fix}]).
-define(esCfgSync, esCfgSync).
-define(esRecompileCnt, '$esRecompileCnt').

+ 8
- 0
rebar.config Прегледај датотеку

@ -0,0 +1,8 @@
{erl_opts, [no_debug_info]}.
{deps, [
]}.
{shell, [
% {config, "config/sys.config"},
{apps, [erlSync]}
]}.

+ 46
- 0
src/erlSync.app.src Прегледај датотеку

@ -0,0 +1,46 @@
{application, erlSync,
[{description, "erlang code auto compile and loader"},
{vsn, "0.1.0"},
{registered, []},
{mod, {erlSync_app, []}},
{applications, [kernel, stdlib, syntax_tools, compiler]},
{env, [
%% 扫描module的间隔时间
{moduleTime, 40000},
%% 扫描 源码目录的间隔时间
{srcDirTime, 6000},
%% 扫描 源码文件的间隔时间
{srcFileTime, 6000},
%% 对比加载beam 文件的间隔时间
{compareBeamTime, 2000},
%% 对比编译erl hrl文件的间隔时间
{compareSrcFileTime, 2000},
%% 编译和加载以及其他一些日志的提示级别设置
%% 有效值: all | none | [success | warnings | errors]
%% 默认值: all
{log, all},
%% 这个参数用于设置特殊目录下的文件检查编译与加载
%% 格式:{srcDirs, {strategy(), [srcDirDescr()]}} | {srcDirs, undefined}
%% -type strategy() :: add | only.
%% 如果 strategy() is only, 仅仅扫描指定目录下的文件编译与加载. 如果 strategy() is add, 会扫描添加的指定目录同步编译与加载.
%% -type srcDirDescr() :: { Dir :: file:filename(), [Options :: compile_option()]}.
%% 默认值:undefined 根据当前工作目录 和 已经加载的模块做来得出需要扫描的目录
{srcDirs, {only, [{"erlSync", []}]}},
%% 这个参数用来设置 怎么处理 当beam文件的源文件目录不是当前工作的子目录时的情况
%% 有效值: fix | allow | ignore
%% * fix = 尝试在当前目录下查找源文件
%% * allow = 不要做任何特别的事情,使用beam源文件原始路径查找该文件
%% * ignore = 而忽略对其源路径的任何更改
%% 默认值: fix
{descendant, fix},
%% 仅仅同步编译和加载该参数指定的模块
%% default: [] 为空的时候 该参数无效
{onlyMods, []},
%% 不同步编译和加载该参数指定的模块
%% default: [] 为空的时候 该参数无效
{excludedMods, []}
]},
{modules, []},
{licenses, ["MIT License"]},
{links, []}
]}.

+ 61
- 0
src/erlSync.erl Прегледај датотеку

@ -0,0 +1,61 @@
-module(erlSync).
-export([
start/0,
stop/0,
run/0,
pause/0,
curInfo/0,
setLog/1,
getLog/0,
getOnsync/0,
setOnsync/0,
setOnsync/1,
swSyncNode/1
]).
start() ->
application:ensure_all_started(erlSync).
stop() ->
application:stop(erlSync).
run() ->
case start() of
{ok, _Started} ->
esScanner:unpause(),
esScanner:rescan(),
ok;
{error, Reason} ->
esUtils:logErrors("start erlSync error ~p~n", [Reason])
end.
pause() ->
esScanner:pause().
swSyncNode(IsSync) ->
run(),
esScanner:swSyncNode(IsSync),
ok.
curInfo() ->
esScanner:curInfo().
setLog(Val) ->
esScanner:setLog(Val).
getLog() ->
esScanner:getLog().
getOnsync() ->
esScanner:getOnsync().
setOnsync() ->
esScanner:setOnsync(undefined).
setOnsync(Fun) ->
esScanner:setOnsync(Fun).

+ 10
- 0
src/erlSync_app.erl Прегледај датотеку

@ -0,0 +1,10 @@
-module(erlSync_app).
-behaviour(application).
-export([start/2, stop/1]).
start(_StartType, _StartArgs) ->
erlSync_sup:start_link().
stop(_State) ->
ok.

+ 27
- 0
src/erlSync_sup.erl Прегледај датотеку

@ -0,0 +1,27 @@
-module(erlSync_sup).
-behaviour(supervisor).
-export([
start_link/0
, init/1
]).
-define(SERVER, ?MODULE).
-define(ChildSpec(I, Type), #{id => I, start => {I, start_link, []}, restart => permanent, shutdown => 5000, type => Type, modules => [I]}).
start_link() ->
supervisor:start_link({local, ?SERVER}, ?MODULE, []).
%% sup_flags() = #{strategy => strategy(), % optional
%% intensity => non_neg_integer(), % optional
%% period => pos_integer()} % optional
%% child_spec() = #{id => child_id(), % mandatory
%% start => mfargs(), % mandatory
%% restart => restart(), % optional
%% shutdown => shutdown(), % optional
%% type => worker(), % optional
%% modules => modules()} % optional
init([]) ->
SupFlags = #{strategy => one_for_one, intensity => 5, period => 10},
ChildSpecs = [?ChildSpec(esScanner, worker)],
{ok, {SupFlags, ChildSpecs}}.

+ 691
- 0
src/sync/esScanner.erl Прегледај датотеку

@ -0,0 +1,691 @@
-module(esScanner).
-include("erlSync.hrl").
-behaviour(gen_server).
-compile(inline).
-compile({inline_size, 128}).
%% API
-export([
start_link/0,
rescan/0,
pause/0,
unpause/0,
setLog/1,
getLog/0,
curInfo/0,
getOnsync/0,
setOnsync/1,
isOnlyDir/2,
swSyncNode/1
]).
%% gen_server callbacks
-export([
init/1,
handle_call/3,
handle_cast/2,
handle_info/2,
terminate/2
]).
-define(SERVER, ?MODULE).
-type timestamp() :: file:date_time() | 0.
-record(state, {
status = running :: running | pause
, modules = [] :: [module()]
, hrlDirs = [] :: [file:filename()]
, srcDirs = [] :: [file:filename()]
, hrlFiles = [] :: [file:filename()]
, srcFiles = [] :: [file:filename()]
, beamTimes = undefined :: [{module(), timestamp()}] | undefined
, hrlFileTimes = undefined :: [{file:filename(), timestamp()}] | undefined
, srcFileTimes = undefined :: [{file:filename(), timestamp()}] | undefined
, onsyncFun = undefined
, swSyncNode = false
}).
%% ************************************ API start ***************************
rescan() ->
gen_server:cast(?SERVER, miCollMods),
gen_server:cast(?SERVER, miCollSrcDirs),
gen_server:cast(?SERVER, miCollSrcFiles),
gen_server:cast(?SERVER, miCompareHrlFiles),
gen_server:cast(?SERVER, miCompareSrcFiles),
gen_server:cast(?SERVER, miCompareBeams),
esUtils:logSuccess("start Scanning source files..."),
ok.
unpause() ->
gen_server:cast(?SERVER, miUnpause),
ok.
pause() ->
gen_server:cast(?SERVER, miPause),
esUtils:logSuccess("Pausing erlSync. Call erlSync:run() to restart"),
ok.
curInfo() ->
gen_server:call(?SERVER, miCurInfo).
setLog(T) when ?LOG_ON(T) ->
esUtils:setEnv(log, T),
loadCfg(),
esUtils:logSuccess("Console Notifications Enabled"),
ok;
setLog(_) ->
esUtils:setEnv(log, none),
loadCfg(),
esUtils:logSuccess("Console Notifications Disabled"),
ok.
getLog() ->
?esCfgSync:getv(log).
swSyncNode(IsSync) ->
gen_server:cast(?SERVER, {miSyncNode, IsSync}),
ok.
getOnsync() ->
gen_server:call(?SERVER, miGetOnsync).
setOnsync(Fun) ->
gen_server:call(?SERVER, {miSetOnsync, Fun}).
%% ************************************ API end ***************************
start_link() ->
gen_server:start_link({local, ?SERVER}, ?MODULE, [], []).
init([]) ->
erlang:process_flag(trap_exit, true),
loadCfg(),
erlang:put(?esRecompileCnt, 0),
{ok, #state{}}.
handle_call(miGetOnsync, _, #state{onsyncFun = OnSync} = State) ->
{reply, OnSync, State};
handle_call({miSetOnsync, Fun}, _, State) ->
{reply, ok, State#state{onsyncFun = Fun}};
handle_call(miCurInfo, _, State) ->
{reply, {erlang:get(), State}, State};
handle_call(_Request, _, State) ->
{reply, ok, State}.
handle_cast(miPause, State) ->
{noreply, State#state{status = pause}};
handle_cast(miUnpause, State) ->
{noreply, State#state{status = running}};
handle_cast(miCollMods, State) ->
AllModules = (erlang:loaded() -- esUtils:getSystemModules()),
LastCollMods = filterCollMods(AllModules),
Time = ?esCfgSync:getv(?moduleTime),
?gTimeout(miCollMods, Time),
{noreply, State#state{modules = LastCollMods}};
handle_cast(miCollSrcDirs, #state{status = running, modules = Modules} = State) ->
{USortedSrcDirs, USortedHrlDirs} =
case ?esCfgSync:getv(srcDirs) of
undefined ->
collSrcDirs(Modules, [], []);
{add, DirsAndOpts} ->
collSrcDirs(Modules, addSrcDirs(DirsAndOpts), []);
{only, DirsAndOpts} ->
collSrcDirs(Modules, [], addSrcDirs(DirsAndOpts))
end,
Time = ?esCfgSync:getv(?srcDirTime),
?gTimeout(miCollSrcDirs, Time),
{noreply, State#state{srcDirs = USortedSrcDirs, hrlDirs = USortedHrlDirs}};
handle_cast(miCollSrcFiles, #state{status = running, hrlDirs = HrlDirs, srcDirs = SrcDirs} = State) ->
FSrc =
fun(Dir, Acc) ->
esUtils:wildcard(Dir, ".*\\.(erl|dtl|lfe|ex)$") ++ Acc
end,
SrcFiles = lists:usort(lists:foldl(FSrc, [], SrcDirs)),
FHrl =
fun(Dir, Acc) ->
esUtils:wildcard(Dir, ".*\\.hrl$") ++ Acc
end,
HrlFiles = lists:usort(lists:foldl(FHrl, [], HrlDirs)),
Time = ?esCfgSync:getv(?srcFileTime),
?gTimeout(miCollSrcFiles, Time),
{noreply, State#state{srcFiles = SrcFiles, hrlFiles = HrlFiles}};
handle_cast(miCompareBeams, #state{status = running, modules = Modules, beamTimes = BeamTimes, onsyncFun = OnsyncFun, swSyncNode = SwSyncNode} = State) ->
BeamTimeList = [{Mod, LastMod} || Mod <- Modules, LastMod <- [modLastmod(Mod)], LastMod =/= 0],
NewBeamLastMod = lists:usort(BeamTimeList),
reloadChangedMod(BeamTimes, NewBeamLastMod, SwSyncNode, OnsyncFun, []),
Time = ?esCfgSync:getv(?compareBeamTime),
?gTimeout(miCompareBeams, Time),
{noreply, State#state{beamTimes = NewBeamLastMod}};
handle_cast(miCompareSrcFiles, #state{status = running, srcFiles = SrcFiles, srcFileTimes = SrcFileTimes, swSyncNode = SwSyncNode} = State) ->
erlang:put(?esRecompileCnt, 0),
%% Create a list of file lastmod times...
SrcFileTimeList = [{Src, LastMod} || Src <- SrcFiles, LastMod <- [filelib:last_modified(Src)], LastMod =/= 0],
%% NewSrcFileLastMod = lists:usort(SrcFileTimeList),
%% Compare to previous results, if there are changes, then recompile the file...
recompileChangeSrcFile(SrcFileTimes, SrcFileTimeList, SwSyncNode),
case erlang:get(?esRecompileCnt) > 0 of
true ->
gen_server:cast(?SERVER, miCompareBeams);
_ ->
ignore
end,
Time = ?esCfgSync:getv(?compareSrcFileTime),
?gTimeout(miCompareSrcFiles, Time),
{noreply, State#state{srcFileTimes = SrcFileTimeList}};
handle_cast(miCompareHrlFiles, #state{status = running, hrlFiles = HrlFiles, srcFiles = SrcFiles, hrlFileTimes = HrlFileTimes, swSyncNode = SwSyncNode} = State) ->
erlang:put(?esRecompileCnt, 0),
%% Create a list of file lastmod times...
HrlFileTimeList = [{Hrl, LastMod} || Hrl <- HrlFiles, LastMod <- [filelib:last_modified(Hrl)], LastMod =/= 0],
%% NewHrlFileLastMod = lists:usort(HrlFileTimeList),
%% Compare to previous results, if there are changes, then recompile src files that depends
recompileChangeHrlFile(HrlFileTimes, HrlFileTimeList, SrcFiles, SwSyncNode),
case erlang:get(?esRecompileCnt) > 0 of
true ->
gen_server:cast(?SERVER, miCompareBeams);
_ ->
ignore
end,
Time = ?esCfgSync:getv(?compareSrcFileTime),
?gTimeout(miCompareHrlFiles, Time),
{noreply, State#state{hrlFileTimes = HrlFileTimeList}};
handle_cast({miSyncNode, IsSync}, State) ->
case IsSync of
true ->
{noreply, State#state{swSyncNode = true}};
_ ->
{noreply, State#state{swSyncNode = false}}
end;
handle_cast(_Msg, State) ->
esUtils:logSuccess("recv unexpect cast msg..."),
{noreply, State}.
handle_info({timeout, _Ref, {doSync, Msg}}, State) ->
erlang:erase({pdTimerRef, Msg}),
handle_cast(Msg, State);
handle_info(_Msg, State) ->
{noreply, State}.
terminate(_Reason, _State) ->
ok.
%% ***********************************PRIVATE FUNCTIONS start *******************************************
addSrcDirs(DirsAndOpts) ->
[
begin
%% ensure module out path exists & in our code path list
case proplists:get_value(outdir, Opts) of
undefined ->
true;
Path ->
ok = filelib:ensure_dir(Path),
true = code:add_pathz(Path)
end,
setOptions(Dir, Opts),
Dir
end || {Dir, Opts} <- DirsAndOpts
].
reloadChangedMod([{Module, LastMod} | T1], [{Module, LastMod} | T2], SwSyncNode, OnsyncFun, Acc) ->
reloadChangedMod(T1, T2, SwSyncNode, OnsyncFun, Acc);
reloadChangedMod([{Module, _} | T1], [{Module, _} | T2], SwSyncNode, OnsyncFun, Acc) ->
case code:get_object_code(Module) of
error ->
Msg = io_lib:format("Error loading object code for ~p", [Module]),
esUtils:logErrors(Msg),
reloadChangedMod(T1, T2, SwSyncNode, OnsyncFun, Acc);
{Module, Binary, Filename} ->
case code:load_binary(Module, Filename, Binary) of
{module, Module} ->
Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Success", [Module]),
esUtils:logSuccess(Msg);
{error, What} ->
Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Errors Reason:~p", [Module, What]),
esUtils:logErrors(Msg)
end,
case SwSyncNode of
true ->
{ok, NumNodes, Nodes} = syncLoadModOnAllNodes(Module),
MsgNodes = io_lib:format("Reloaded(Beam changed) Mod:~s on ~p nodes:~p", [Module, NumNodes, Nodes]),
esUtils:logSuccess(MsgNodes);
false ->
ignore
end,
reloadChangedMod(T1, T2, SwSyncNode, OnsyncFun, [Module | Acc])
end;
reloadChangedMod([{Module1, _LastMod1} | T1] = OldLastMods, [{Module2, _LastMod2} | T2] = NewLastMods, SwSyncNode, OnsyncFun, Acc) ->
%% Lists are different, advance the smaller one...
case Module1 < Module2 of
true ->
reloadChangedMod(T1, NewLastMods, SwSyncNode, OnsyncFun, Acc);
false ->
reloadChangedMod(OldLastMods, T2, SwSyncNode, OnsyncFun, Acc)
end;
reloadChangedMod(A, B, _SwSyncNode, OnsyncFun, Acc) when A =:= []; B =:= [] ->
fireOnsync(OnsyncFun, Acc),
ok;
reloadChangedMod(undefined, _Other, _, _, _) ->
ok.
fireOnsync(OnsyncFun, Modules) ->
case OnsyncFun of
undefined -> ok;
Funs when is_list(Funs) -> onsyncApplyList(Funs, Modules);
Fun -> onsyncApply(Fun, Modules)
end.
onsyncApplyList(Funs, Modules) ->
[onsyncApply(Fun, Modules) || Fun <- Funs].
onsyncApply({M, F}, Modules) ->
erlang:apply(M, F, [Modules]);
onsyncApply(Fun, Modules) when is_function(Fun) ->
Fun(Modules).
getNodes() ->
lists:usort(lists:flatten(nodes() ++ [rpc:call(X, erlang, nodes, []) || X <- nodes()])) -- [node()].
syncLoadModOnAllNodes(Module) ->
%% Get a list of nodes known by this node, plus all attached nodes.
Nodes = getNodes(),
NumNodes = length(Nodes),
{Module, Binary, _} = code:get_object_code(Module),
FSync =
fun(Node) ->
MsgNode = io_lib:format("Reloading '~s' on ~p", [Module, Node]),
esUtils:logSuccess(MsgNode),
rpc:call(Node, code, ensure_loaded, [Module]),
case rpc:call(Node, code, which, [Module]) of
Filename when is_binary(Filename) orelse is_list(Filename) ->
%% File exists, overwrite and load into VM.
ok = rpc:call(Node, file, write_file, [Filename, Binary]),
rpc:call(Node, code, purge, [Module]),
case rpc:call(Node, code, load_file, [Module]) of
{module, Module} ->
Msg = io_lib:format("Reloaded(Beam changed) Mod:~s and write Success on node:~p", [Module, Node]),
esUtils:logSuccess(Msg);
{error, What} ->
Msg = io_lib:format("Reloaded(Beam changed) Mod:~s and write Errors on node:~p Reason:~p", [Module, Node, What]),
esUtils:logErrors(Msg)
end;
_ ->
%% File doesn't exist, just load into VM.
case rpc:call(Node, code, load_binary, [Module, undefined, Binary]) of
{module, Module} ->
Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Success on node:~p", [Module, Node]),
esUtils:logSuccess(Msg);
{error, What} ->
Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Errors on node:~p Reason:~p", [Module, Node, What]),
esUtils:logErrors(Msg)
end
end
end,
[FSync(X) || X <- Nodes],
{ok, NumNodes, Nodes}.
recompileChangeSrcFile([{File, LastMod} | T1], [{File, LastMod} | T2], SwSyncNode) ->
recompileChangeSrcFile(T1, T2, SwSyncNode);
recompileChangeSrcFile([{File, _} | T1], [{File, _} | T2], SwSyncNode) ->
recompileSrcFile(File, SwSyncNode),
recompileChangeSrcFile(T1, T2, SwSyncNode);
recompileChangeSrcFile([{File1, _LastMod1} | T1] = OldSrcFiles, [{File2, LastMod2} | T2] = NewSrcFiles, SwSyncNode) ->
%% Lists are different...
case File1 < File2 of
true ->
%% File was removed, do nothing...
recompileChangeSrcFile(T1, NewSrcFiles, SwSyncNode);
false ->
maybeRecompileSrcFile(File2, LastMod2, SwSyncNode),
recompileChangeSrcFile(OldSrcFiles, T2, SwSyncNode)
end;
recompileChangeSrcFile([], [{File, LastMod} | T2], SwSyncNode) ->
maybeRecompileSrcFile(File, LastMod, SwSyncNode),
recompileChangeSrcFile([], T2, SwSyncNode);
recompileChangeSrcFile(_A, [], _) ->
%% All remaining files, if any, were removed.
ok;
recompileChangeSrcFile(undefined, _Other, _) ->
ok.
erlydtlCompile(SrcFile, Options) ->
F =
fun({outdir, OutDir}, Acc) -> [{out_dir, OutDir} | Acc];
(OtherOption, Acc) -> [OtherOption | Acc]
end,
DtlOptions = lists:foldl(F, [], Options),
Module = list_to_atom(lists:flatten(filename:basename(SrcFile, ".dtl") ++ "_dtl")),
Compiler = erlydtl,
Compiler:compile(SrcFile, Module, DtlOptions).
elixir_compile(SrcFile, Options) ->
Outdir = proplists:get_value(outdir, Options),
Compiler = ':Elixir.Kernel.ParallelCompiler',
Modules = Compiler:files_to_path([list_to_binary(SrcFile)], list_to_binary(Outdir)),
Loader =
fun(Module) ->
Outfile = code:which(Module),
Binary = file:read_file(Outfile),
{Module, Binary}
end,
Results = lists:map(Loader, Modules),
{ok, multiple, Results, []}.
lfe_compile(SrcFile, Options) ->
Compiler = lfe_comp,
Compiler:file(SrcFile, Options).
maybeRecompileSrcFile(File, LastMod, SwSyncNode) ->
Module = list_to_atom(filename:basename(File, ".erl")),
case code:which(Module) of
BeamFile when is_list(BeamFile) ->
%% check with beam file
case filelib:last_modified(BeamFile) of
BeamLastMod when LastMod > BeamLastMod ->
recompileSrcFile(File, SwSyncNode);
_ ->
ok
end;
_ ->
%% File is new, recompile...
recompileSrcFile(File, SwSyncNode)
end.
getCompileFunAndModuleName(SrcFile) ->
case esUtils:getFileType(SrcFile) of
erl ->
{fun compile:file/2, list_to_atom(filename:basename(SrcFile, ".erl"))};
dtl ->
{fun erlydtlCompile/2, list_to_atom(lists:flatten(filename:basename(SrcFile, ".dtl") ++ "_dtl"))};
lfe ->
{fun lfe_compile/2, list_to_atom(filename:basename(SrcFile, ".lfe"))};
elixir ->
{fun elixir_compile/2, list_to_atom(filename:basename(SrcFile, ".ex"))}
end.
getObjectCode(Module) ->
case code:get_object_code(Module) of
{Module, B, _Filename} -> B;
_ -> undefined
end.
reloadIfNecessary(_CompileFun, _SrcFile, _Module, Binary, Binary, _Options) ->
ok;
reloadIfNecessary(CompileFun, SrcFile, Module, _OldBinary, _Binary, Options) ->
%% Compiling changed the beam code. Compile and reload.
CompileFun(SrcFile, Options),
%% Try to load the module...
case code:ensure_loaded(Module) of
{module, Module} -> ok;
{error, nofile} -> errorNoFile(Module);
{error, embedded} ->
case code:load_file(Module) of %% Module is not yet loaded, load it.
{module, Module} -> ok;
{error, nofile} -> errorNoFile(Module)
end
end,
erlang:put(?esRecompileCnt, erlang:get(?esRecompileCnt) + 1).
errorNoFile(Module) ->
Msg = io_lib:format("~p Couldn't load module: nofile", [Module]),
esUtils:logWarnings([Msg]).
recompileSrcFile(SrcFile, SwSyncNode) ->
%% Get the module, src dir, and options...
case esUtils:getSrcDir(SrcFile) of
{ok, SrcDir} ->
{CompileFun, Module} = getCompileFunAndModuleName(SrcFile),
OldBinary = getObjectCode(Module),
case getOptions(SrcDir) of
{ok, Options} ->
case CompileFun(SrcFile, [binary, return | Options]) of
{ok, Module, Binary, Warnings} ->
reloadIfNecessary(CompileFun, SrcFile, Module, OldBinary, Binary, Options),
printResults(Module, SrcFile, [], Warnings),
{ok, [], Warnings};
{ok, [{ok, Module, Binary, Warnings}], Warnings2} ->
reloadIfNecessary(CompileFun, SrcFile, Module, OldBinary, Binary, Options),
printResults(Module, SrcFile, [], Warnings ++ Warnings2),
{ok, [], Warnings ++ Warnings2};
{ok, multiple, Results, Warnings} ->
[reloadIfNecessary(CompileFun, SrcFile, CompiledModule, OldBinary, Binary, Options) || {CompiledModule, Binary} <- Results],
printResults(Module, SrcFile, [], Warnings),
{ok, [], Warnings};
{ok, OtherModule, _Binary, Warnings} ->
Desc = io_lib:format("Module definition (~p) differs from expected (~s)", [OtherModule, filename:rootname(filename:basename(SrcFile))]),
Errors = [{SrcFile, {0, Module, Desc}}],
printResults(Module, SrcFile, Errors, Warnings),
{ok, Errors, Warnings};
{error, Errors, Warnings} ->
printResults(Module, SrcFile, Errors, Warnings),
{ok, Errors, Warnings}
end;
undefined ->
case esUtils:tryGetModOptions(Module) of
{ok, Options} ->
setOptions(SrcDir, Options),
recompileSrcFile(SrcFile, SwSyncNode);
_ ->
Msg = io_lib:format("Unable to determine options for ~s", [SrcFile]),
esUtils:logErrors(Msg)
end
end;
_ ->
Msg = io_lib:format("not find the file ~s", [SrcFile]),
esUtils:logErrors(Msg)
end.
printResults(_Module, SrcFile, [], []) ->
Msg = io_lib:format("~s Recompiled", [SrcFile]),
esUtils:logSuccess(lists:flatten(Msg));
printResults(_Module, SrcFile, [], Warnings) ->
Msg = [formatErrors(SrcFile, [], Warnings), io_lib:format("~s Recompiled with ~p warnings", [SrcFile, length(Warnings)])],
esUtils:logWarnings(Msg);
printResults(_Module, SrcFile, Errors, Warnings) ->
Msg = [formatErrors(SrcFile, Errors, Warnings)],
esUtils:logErrors(Msg).
%% @private Print error messages in a pretty and user readable way.
formatErrors(File, Errors, Warnings) ->
AllErrors1 = lists:sort(lists:flatten([X || {_, X} <- Errors])),
AllErrors2 = [{Line, "Error", Module, Description} || {Line, Module, Description} <- AllErrors1],
AllWarnings1 = lists:sort(lists:flatten([X || {_, X} <- Warnings])),
AllWarnings2 = [{Line, "Warning", Module, Description} || {Line, Module, Description} <- AllWarnings1],
Everything = lists:sort(AllErrors2 ++ AllWarnings2),
FPck =
fun({Line, Prefix, Module, ErrorDescription}) ->
Msg = formatError(Module, ErrorDescription),
io_lib:format("~s:~p: ~s: ~s", [File, Line, Prefix, Msg])
end,
[FPck(X) || X <- Everything].
formatError(Module, ErrorDescription) ->
case erlang:function_exported(Module, format_error, 1) of
true -> Module:format_error(ErrorDescription);
false -> io_lib:format("~s", [ErrorDescription])
end.
recompileChangeHrlFile([{File, LastMod} | T1], [{File, LastMod} | T2], SrcFiles, SwSyncNode) ->
recompileChangeHrlFile(T1, T2, SrcFiles, SwSyncNode);
recompileChangeHrlFile([{File, _} | T1], [{File, _} | T2], SrcFiles, SwSyncNode) ->
WhoInclude = whoInclude(File, SrcFiles),
[recompileSrcFile(SrcFile, SwSyncNode) || SrcFile <- WhoInclude],
recompileChangeHrlFile(T1, T2, SrcFiles, SwSyncNode);
recompileChangeHrlFile([{File1, _LastMod1} | T1] = OldHrlFiles, [{File2, LastMod2} | T2] = NewHrlFiles, SrcFiles, SwSyncNode) ->
%% Lists are different...
case File1 < File2 of
true ->
%% File was removed, do nothing...
warnDelHrlFiles(File1, SrcFiles),
recompileChangeHrlFile(T1, NewHrlFiles, SrcFiles, SwSyncNode);
false ->
%% File is new, look for src that include it
WhoInclude = whoInclude(File2, SrcFiles),
[maybeRecompileSrcFile(SrcFile, LastMod2, SwSyncNode) || SrcFile <- WhoInclude],
recompileChangeHrlFile(OldHrlFiles, T2, SrcFiles, SwSyncNode)
end;
recompileChangeHrlFile([], [{File, LastMod} | T2], SrcFiles, SwSyncNode) ->
WhoInclude = whoInclude(File, SrcFiles),
[maybeRecompileSrcFile(SrcFile, LastMod, SwSyncNode) || SrcFile <- WhoInclude],
recompileChangeHrlFile([], T2, SrcFiles, SwSyncNode);
recompileChangeHrlFile([{File1, _LastMod1} | T1], [], SrcFiles, SwSyncNode) ->
warnDelHrlFiles(File1, SrcFiles),
recompileChangeHrlFile(T1, [], SrcFiles, SwSyncNode);
recompileChangeHrlFile([], [], _, _) ->
%% Done
ok;
recompileChangeHrlFile(undefined, _Other, _, _) ->
%% First load, do nothing
ok.
warnDelHrlFiles(HrlFile, SrcFiles) ->
WhoInclude = whoInclude(HrlFile, SrcFiles),
case WhoInclude of
[] -> ok;
_ ->
Msg = io_lib:format("Warning. Deleted ~p file included in existing src files: ~p", [filename:basename(HrlFile), lists:map(fun(File) ->
filename:basename(File) end, WhoInclude)]),
esUtils:logSuccess(lists:flatten(Msg))
end.
whoInclude(HrlFile, SrcFiles) ->
HrlFileBaseName = filename:basename(HrlFile),
Pred =
fun(SrcFile) ->
{ok, Forms} = epp_dodger:parse_file(SrcFile),
isInclude(HrlFileBaseName, Forms)
end,
lists:filter(Pred, SrcFiles).
isInclude(_HrlFile, []) ->
false;
isInclude(HrlFile, [{tree, attribute, _, {attribute, _, [{_, _, IncludeFile}]}} | Forms]) when is_list(IncludeFile) ->
IncludeFileBaseName = filename:basename(IncludeFile),
case IncludeFileBaseName of
HrlFile -> true;
_ -> isInclude(HrlFile, Forms)
end;
isInclude(HrlFile, [_SomeForm | Forms]) ->
isInclude(HrlFile, Forms).
filterCollMods(Modules) ->
excludeMods(onlyMods(Modules)).
onlyMods(Modules) ->
case ?esCfgSync:getv(?onlyMods) of
[] ->
Modules;
OnlyMods ->
[Mod || Mod <- Modules, checkModIsMatch(OnlyMods, Mod) == true]
end.
excludeMods(Modules) ->
case ?esCfgSync:getv(?excludedMods) of
[] ->
Modules;
ExcludedModules ->
[Mod || Mod <- Modules, checkModIsMatch(ExcludedModules, Mod) == false]
end.
checkModIsMatch([], _Module) ->
false;
checkModIsMatch([ModOrPattern | T], Module) ->
case ModOrPattern of
Module ->
true;
_ when is_list(ModOrPattern) ->
case re:run(atom_to_list(Module), ModOrPattern) of
{match, _} ->
true;
nomatch ->
checkModIsMatch(T, Module)
end;
_ ->
checkModIsMatch(T, Module)
end.
collSrcDirs(Modules, AddDirs, OnlyDirs) ->
FColl =
fun
(Mod, {SrcAcc, HrlAcc} = Acc) ->
case esUtils:getModSrcDir(Mod) of
{ok, SrcDir} ->
case isOnlyDir(OnlyDirs, SrcDir) of
true ->
{ok, Options} = esUtils:getModOptions(Mod),
HrlDir = proplists:get_all_values(i, Options),
setOptions(SrcDir, Options),
{[SrcDir | SrcAcc], HrlDir ++ HrlAcc};
_ ->
Acc
end;
undefined ->
Acc
end
end,
{SrcDirs, HrlDirs} = lists:foldl(FColl, {AddDirs, []}, Modules),
USortedSrcDirs = lists:usort(SrcDirs),
USortedHrlDirs = lists:usort(HrlDirs),
{USortedSrcDirs, USortedHrlDirs}.
isOnlyDir([], _) ->
true;
isOnlyDir(ReplaceDirs, SrcDir) ->
isMatchDir(ReplaceDirs, SrcDir).
isMatchDir([], _SrcDir) ->
false;
isMatchDir([SrcDir | _ReplaceDirs], SrcDir) ->
true;
isMatchDir([OneDir | ReplaceDirs], SrcDir) ->
case re:run(SrcDir, OneDir) of
nomatch -> isMatchDir(ReplaceDirs, SrcDir);
_ -> true
end.
modLastmod(Mod) ->
case code:which(Mod) of
Beam when is_list(Beam) ->
filelib:last_modified(Beam);
_Other ->
0 %% non_existing | cover_compiled | preloaded
end.
getOptions(SrcDir) ->
case erlang:get(SrcDir) of
undefined ->
undefined;
Options ->
{ok, Options}
end.
setOptions(SrcDir, Options) ->
case erlang:get(SrcDir) of
undefined ->
erlang:put(SrcDir, Options);
OldOptions ->
NewOptions =
case lists:keytake(compile_info, 1, Options) of
{value, {compile_info, ValList1}, Options1} ->
case lists:keytake(compile_info, 1, OldOptions) of
{value, {compile_info, ValList2}, Options2} ->
[{compile_info, lists:usort(ValList1 ++ ValList2)} | lists:usort(Options1 ++ Options2)];
_ ->
lists:usort(Options ++ OldOptions)
end;
_ ->
lists:usort(Options ++ OldOptions)
end,
erlang:put(SrcDir, NewOptions)
end.
loadCfg() ->
KVs = [{Key, esUtils:getEnv(Key, DefVal)} || {Key, DefVal} <- ?CfgList],
esUtils:load(?esCfgSync, KVs).
%% ***********************************PRIVATE FUNCTIONS end *********************************************

+ 356
- 0
src/sync/esUtils.erl Прегледај датотеку

@ -0,0 +1,356 @@
-module(esUtils).
-include("erlSync.hrl").
-compile(inline).
-compile({inline_size, 128}).
-export([
getModSrcDir/1,
getModOptions/1,
getFileType/1,
getSrcDir/1,
wildcard/2,
getEnv/2,
setEnv/2,
load/2,
logSuccess/1,
logErrors/1,
logWarnings/1,
getSystemModules/0,
tryGetModOptions/1
]).
getModSrcDir(Module) ->
case code:is_loaded(Module) of
{file, _} ->
try
%% Get some module info...
Props = Module:module_info(compile),
Source = proplists:get_value(source, Props, ""),
%% Ensure that the file exists, is a decendent of the tree, and how to deal with that
IsFile = filelib:is_regular(Source),
IsDescendant = isDescendent(Source),
Descendant = ?esCfgSync:getv(?descendant),
LastSource =
case {IsFile, IsDescendant, Descendant} of
%% is file and descendant, we're good to go
{true, true, _} -> Source;
%% is not a descendant, but we allow them, so good to go
{true, false, allow} -> Source;
%% is not a descendant, and we fix non-descendants, so let's fix it
{_, false, fix} -> fixDescendantSource(Source, IsFile);
%% Anything else, and we don't know what to do, so let's just bail.
_ -> undefined
end,
case LastSource of
undefined ->
undefined;
_ ->
%% Get the source dir...
Dir = filename:dirname(LastSource),
getSrcDir(Dir)
end
catch _ : _ ->
undefined
end;
_ ->
undefined
end.
getModOptions(Module) ->
case code:is_loaded(Module) of
{file, _} ->
try
Props = Module:module_info(compile),
BeamDir = filename:dirname(code:which(Module)),
Options1 = proplists:get_value(options, Props, []),
%% transform `outdir'
Options2 = transformOutdir(BeamDir, Options1),
Options3 = ensureInclude(Options2),
%% transform the include directories
Options4 = transformAllIncludes(Module, BeamDir, Options3),
%% maybe_add_compile_info
Options5 = maybeAddCompileInfo(Options4),
%% add filetype to options (DTL, LFE, erl, etc)
Options6 = addFileType(Module, Options5),
{ok, Options6}
catch ExType:Error ->
Msg = [io_lib:format("~p:0: ~p looking for options: ~p. Stack: ~p~n", [Module, ExType, Error, erlang:get_stacktrace()])],
logWarnings(Msg),
{ok, []}
end;
_ ->
{ok, []}
end.
tryGetModOptions(Module) ->
try
Props = Module:module_info(compile),
BeamDir = filename:dirname(code:which(Module)),
Options1 = proplists:get_value(options, Props, []),
%% transform `outdir'
Options2 = transformOutdir(BeamDir, Options1),
Options3 = ensureInclude(Options2),
%% transform the include directories
Options4 = transformAllIncludes(Module, BeamDir, Options3),
%% maybe_add_compile_info
Options5 = maybeAddCompileInfo(Options4),
%% add filetype to options (DTL, LFE, erl, etc)
Options6 = addFileType(Module, Options5),
{ok, Options6}
catch _ExType:_Error ->
undefiend
end.
transformOutdir(BeamDir, Options) ->
[{outdir, BeamDir} | proplists:delete(outdir, Options)].
ensureInclude(Options) ->
case proplists:get_value(i, Options) of
undefined -> [{i, "include"} | Options];
_ -> Options
end.
transformAllIncludes(Module, BeamDir, Options) ->
[transformInclude(Module, BeamDir, Opt) || Opt <- Options].
transformInclude(Module, BeamDir, {i, IncludeDir}) ->
{ok, SrcDir} = getModSrcDir(Module),
{ok, IncludeDir2} = determineIncludeDir(IncludeDir, BeamDir, SrcDir),
{i, IncludeDir2};
transformInclude(_, _, Other) ->
Other.
maybeAddCompileInfo(Options) ->
case lists:member(compile_info, Options) of
true -> Options;
false -> addCompileInfo(Options)
end.
addCompileInfo(Options) ->
CompInfo = [{K, V} || {K, V} <- Options, lists:member(K, [outdir, i])],
[{compile_info, CompInfo} | Options].
addFileType(Module, Options) ->
Type = getFileType(Module),
[{type, Type} | Options].
%% This will check if the given module or source file is an ErlyDTL template.
%% Currently, this is done by checking if its reported source path ends with
%% ".dtl.erl".
getFileType(Module) when is_atom(Module) ->
Props = Module:module_info(compile),
Source = proplists:get_value(source, Props, ""),
getFileType(Source);
getFileType(Source) when is_list(Source) ->
Ext = filename:extension(Source),
Root = filename:rootname(Source),
SecondExt = filename:extension(Root),
case Ext of
".erl" when SecondExt =:= ".dtl" -> dtl;
".dtl" -> dtl;
".erl" -> erl;
".lfe" -> lfe;
".ex" -> elixir
end.
%% This will search back to find an appropriate include directory, by
%% searching further back than "..". Instead, it will extract the basename
%% (probably "include" from the include pathfile, and then search backwards in
%% the directory tree until it finds a directory with the same basename found
%% above.
determineIncludeDir(IncludeDir, BeamDir, SrcDir) ->
IncludeBase = filename:basename(IncludeDir),
case determineIncludeDirFromBeamDir(IncludeBase, IncludeDir, BeamDir) of
{ok, D} -> {ok, D};
undefined ->
{ok, Cwd} = file:get_cwd(),
% Cwd2 = normalizeCaseWindowsDir(Cwd),
% SrcDir2 = normalizeCaseWindowsDir(SrcDir),
% IncludeBase2 = normalizeCaseWindowsDir(IncludeBase),
case findIncludeDirFromAncestors(Cwd, IncludeBase, SrcDir) of
{ok, D} -> {ok, D};
undefined -> {ok, IncludeDir} %% Failed, just stick with original
end
end.
%% First try to see if we have an include file alongside our ebin directory, which is typically the case
determineIncludeDirFromBeamDir(IncludeBase, IncludeDir, BeamDir) ->
BeamBasedIncDir = filename:join(filename:dirname(BeamDir), IncludeBase),
case filelib:is_dir(BeamBasedIncDir) of
true -> {ok, BeamBasedIncDir};
false ->
BeamBasedIncDir2 = filename:join(filename:dirname(BeamDir), IncludeDir),
case filelib:is_dir(BeamBasedIncDir2) of
true -> {ok, BeamBasedIncDir2};
_ ->
undefined
end
end.
%% Then we dig back through the parent directories until we find our include directory
findIncludeDirFromAncestors(Cwd, _, Cwd) -> undefined;
findIncludeDirFromAncestors(_, _, "/") -> undefined;
findIncludeDirFromAncestors(_, _, ".") -> undefined;
findIncludeDirFromAncestors(_, _, "") -> undefined;
findIncludeDirFromAncestors(Cwd, IncludeBase, Dir) ->
NewDirName = filename:dirname(Dir),
AttemptDir = filename:join(NewDirName, IncludeBase),
case filelib:is_dir(AttemptDir) of
true ->
{ok, AttemptDir};
false ->
case NewDirName =/= Dir of
true ->
findIncludeDirFromAncestors(Cwd, IncludeBase, NewDirName);
_ ->
undefined
end
end.
% normalizeCaseWindowsDir(Dir) ->
% case os:type() of
% {win32, _} -> Dir; %string:to_lower(Dir);
% {unix, _} -> Dir
% end.
%% This is an attempt to intelligently fix paths in modules when a
%% release is moved. Essentially, it takes a module name and its original path
%% from Module:module_info(compile), say
%% "/some/original/path/site/src/pages/somepage.erl", and then breaks down the
%% path one by one prefixing it with the current working directory until it
%% either finds a match, or fails. If it succeeds, it returns the Path to the
%% new Source file.
fixDescendantSource([], _IsFile) ->
undefined;
fixDescendantSource(Path, IsFile) ->
{ok, Cwd} = file:get_cwd(),
PathParts = filename:split(Path),
case makeDescendantSource(Cwd, PathParts) of
undefined -> case IsFile of true -> Path; _ -> undefined end;
FoundPath -> FoundPath
end.
makeDescendantSource(_Cwd, []) ->
undefined;
makeDescendantSource(Cwd, [_ | T]) ->
PathAttempt = filename:join([Cwd | T]),
case filelib:is_regular(PathAttempt) of
true -> PathAttempt;
false -> makeDescendantSource(Cwd, T)
end.
isDescendent(Path) ->
{ok, Cwd} = file:get_cwd(),
lists:sublist(Path, length(Cwd)) == Cwd.
%% @private Find the src directory for the specified Directory; max 15 iterations
getSrcDir(Dir) ->
getSrcDir(Dir, 15).
getSrcDir(_Dir, 0) ->
undefined;
getSrcDir(Dir, Ctr) ->
HasCode = filelib:wildcard("*.erl", Dir) /= [] orelse
filelib:wildcard("*.hrl", Dir) /= [] orelse
filelib:wildcard("*.dtl", Dir) /= [] orelse
filelib:wildcard("*.lfe", Dir) /= [] orelse
filelib:wildcard("*.ex", Dir) /= [],
if
HasCode -> {ok, Dir};
true -> getSrcDir(filename:dirname(Dir), Ctr - 1)
end.
%% Return all files in a directory matching a regex.
wildcard(Dir, Regex) ->
filelib:fold_files(Dir, Regex, true, fun(Y, Acc) -> [Y | Acc] end, []).
getEnv(Var, Default) ->
case application:get_env(erlSync, Var) of
{ok, Value} ->
Value;
_ ->
Default
end.
setEnv(Var, Val) ->
ok = application:set_env(erlSync, Var, Val).
logSuccess(Message) ->
canLog(success) andalso error_logger:info_msg(lists:flatten(Message)).
logErrors(Message) ->
canLog(errors) andalso error_logger:error_msg(lists:flatten(Message)).
logWarnings(Message) ->
canLog(warnings) andalso error_logger:warning_msg(lists:flatten(Message)).
canLog(MsgType) ->
case esScanner:getLog() of
true -> true;
all -> true;
none -> false;
false -> false;
skip_success -> MsgType == errors orelse MsgType == warnings;
L when is_list(L) -> lists:member(MsgType, L);
_ -> false
end.
%% Return a list of all modules that belong to Erlang rather than whatever application we may be running.
getSystemModules() ->
Apps = [
appmon, asn1, common_test, compiler, crypto, debugger,
dialyzer, docbuilder, edoc, erl_interface, erts, et,
eunit, gs, hipe, inets, inets, inviso, jinterface, kernel,
mnesia, observer, orber, os_mon, parsetools, percept, pman,
reltool, runtime_tools, sasl, snmp, ssl, stdlib, syntax_tools,
test_server, toolbar, tools, tv, webtool, wx, xmerl, zlib, rebar, rebar3
],
FAppMod =
fun(App) ->
case application:get_key(App, modules) of
{ok, Modules} -> Modules;
_Other -> []
end
end,
lists:flatten([FAppMod(X) || X <- Apps]).
%% map类型的数据不能当做key
-type key() :: atom() | binary() | bitstring() | float() | integer() | list() | tuple().
-type value() :: atom() | binary() | bitstring() | float() | integer() | list() | tuple() | map().
-spec load(term(), [{key(), value()}]) -> ok.
load(Module, KVs) ->
Forms = forms(Module, KVs),
{ok, Module, Bin} = compile:forms(Forms),
code:soft_purge(Module),
{module, Module} = code:load_binary(Module, atom_to_list(Module), Bin),
ok.
forms(Module, KVs) ->
%% -module(Module).
Mod = erl_syntax:attribute(erl_syntax:atom(module), [erl_syntax:atom(Module)]),
%% -export([getv/0]).
ExportList = [erl_syntax:arity_qualifier(erl_syntax:atom(getv), erl_syntax:integer(1))],
Export = erl_syntax:attribute(erl_syntax:atom(export), [erl_syntax:list(ExportList)]),
%% getv(K) -> V
Function = erl_syntax:function(erl_syntax:atom(getv), lookup_clauses(KVs, [])),
[erl_syntax:revert(X) || X <- [Mod, Export, Function]].
lookup_clause(Key, Value) ->
Var = erl_syntax:abstract(Key),
Body = erl_syntax:abstract(Value),
erl_syntax:clause([Var], [], [Body]).
lookup_clause_anon() ->
Var = erl_syntax:variable("_"),
Body = erl_syntax:atom(undefined),
erl_syntax:clause([Var], [], [Body]).
lookup_clauses([], Acc) ->
lists:reverse(lists:flatten([lookup_clause_anon() | Acc]));
lookup_clauses([{Key, Value} | T], Acc) ->
lookup_clauses(T, [lookup_clause(Key, Value) | Acc]).

Loading…
Откажи
Сачувај