erlang自动编译与加载
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

691 line
25 KiB

5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
5 年之前
  1. -module(esScanner).
  2. -include("erlSync.hrl").
  3. -behaviour(gen_ipc).
  4. -compile(inline).
  5. -compile({inline_size, 128}).
  6. %% API
  7. -export([
  8. start_link/0,
  9. rescan/0,
  10. pause/0,
  11. unpause/0,
  12. setLog/1,
  13. getLog/0,
  14. curInfo/0,
  15. getOnsync/0,
  16. setOnsync/1,
  17. swSyncNode/1
  18. ]).
  19. %% gen_ipc callbacks
  20. -export([
  21. init/1,
  22. handleCall/4,
  23. handleCast/3,
  24. handleInfo/3,
  25. handleOnevent/4,
  26. terminate/3
  27. ]).
  28. -define(SERVER, ?MODULE).
  29. -type timestamp() :: file:date_time() | 0.
  30. -record(state, {
  31. modules = [] :: [module()]
  32. , hrlDirs = [] :: [file:filename()]
  33. , srcDirs = [] :: [file:filename()]
  34. , hrlFiles = [] :: [file:filename()]
  35. , srcFiles = [] :: [file:filename()]
  36. , beamTimes = undefined :: [{module(), timestamp()}] | undefined
  37. , hrlFileTimes = undefined :: [{file:filename(), timestamp()}] | undefined
  38. , srcFileTimes = undefined :: [{file:filename(), timestamp()}] | undefined
  39. , onsyncFun = undefined
  40. , swSyncNode = false
  41. }).
  42. %% ************************************ API start ***************************
  43. rescan() ->
  44. gen_ipc:cast(?SERVER, miCollMods),
  45. gen_ipc:cast(?SERVER, miCollSrcDirs),
  46. gen_ipc:cast(?SERVER, miCollSrcFiles),
  47. gen_ipc:cast(?SERVER, miCompareHrlFiles),
  48. gen_ipc:cast(?SERVER, miCompareSrcFiles),
  49. gen_ipc:cast(?SERVER, miCompareBeams),
  50. esUtils:logSuccess("start Scanning source files..."),
  51. ok.
  52. unpause() ->
  53. gen_ipc:cast(?SERVER, miUnpause),
  54. ok.
  55. pause() ->
  56. gen_ipc:cast(?SERVER, miPause),
  57. esUtils:logSuccess("Pausing erlSync. Call erlSync:run() to restart"),
  58. ok.
  59. curInfo() ->
  60. gen_ipc:call(?SERVER, miCurInfo).
  61. setLog(T) when ?LOG_ON(T) ->
  62. esUtils:setEnv(log, T),
  63. loadCfg(),
  64. esUtils:logSuccess("Console Notifications Enabled"),
  65. ok;
  66. setLog(_) ->
  67. esUtils:setEnv(log, none),
  68. loadCfg(),
  69. esUtils:logSuccess("Console Notifications Disabled"),
  70. ok.
  71. getLog() ->
  72. ?esCfgSync:getv(log).
  73. swSyncNode(IsSync) ->
  74. gen_ipc:cast(?SERVER, {miSyncNode, IsSync}),
  75. ok.
  76. getOnsync() ->
  77. gen_ipc:call(?SERVER, miGetOnsync).
  78. setOnsync(Fun) ->
  79. gen_ipc:call(?SERVER, {miSetOnsync, Fun}).
  80. %% ************************************ API end ***************************
  81. start_link() ->
  82. gen_ipc:start_link({local, ?SERVER}, ?MODULE, [], []).
  83. %% status :: running | pause
  84. init([]) ->
  85. erlang:process_flag(trap_exit, true),
  86. loadCfg(),
  87. case persistent_term:get(?esRecompileCnt, undefined) of
  88. undefined ->
  89. IndexRef = atomics:new(1, [{signed, false}]),
  90. persistent_term:put(?esRecompileCnt, IndexRef);
  91. _ ->
  92. ignore
  93. end,
  94. {ok, running, #state{}}.
  95. handleCall(miGetOnsync, _, #state{onsyncFun = OnSync} = State, _From) ->
  96. {reply, OnSync, State};
  97. handleCall({miSetOnsync, Fun}, _, State, _From) ->
  98. {reply, ok, State#state{onsyncFun = Fun}};
  99. handleCall(miCurInfo, _, State, _Form) ->
  100. {reply, {erlang:get(), State}, State};
  101. handleCall(_Request, _, _State, _From) ->
  102. keepStatusState.
  103. handleCast(miPause, _, State) ->
  104. {nextStatus, pause, State};
  105. handleCast(miUnpause, _, State) ->
  106. {nextStatus, running, State};
  107. handleCast(miCollMods, running, State) ->
  108. AllModules = (erlang:loaded() -- esUtils:getSystemModules()),
  109. LastCollMods = filterCollMods(AllModules),
  110. Time = ?esCfgSync:getv(?moduleTime),
  111. {keepStatus, State#state{modules = LastCollMods}, [?gTimeout(miCollMods, Time)]};
  112. handleCast(miCollSrcDirs, running, #state{modules = Modules} = State) ->
  113. {USortedSrcDirs, USortedHrlDirs} =
  114. case ?esCfgSync:getv(srcDirs) of
  115. undefined ->
  116. collSrcDirs(Modules, [], []);
  117. {add, DirsAndOpts} ->
  118. collSrcDirs(Modules, addSrcDirs(DirsAndOpts), []);
  119. {only, DirsAndOpts} ->
  120. collSrcDirs(Modules, [], addSrcDirs(DirsAndOpts))
  121. end,
  122. Time = ?esCfgSync:getv(?srcDirTime),
  123. {keepStatus, State#state{srcDirs = USortedSrcDirs, hrlDirs = USortedHrlDirs}, [?gTimeout(miCollSrcDirs, Time)]};
  124. handleCast(miCollSrcFiles, running, #state{hrlDirs = HrlDirs, srcDirs = SrcDirs} = State) ->
  125. FSrc =
  126. fun(Dir, Acc) ->
  127. esUtils:wildcard(Dir, ".*\\.(erl|dtl|lfe|ex)$") ++ Acc
  128. end,
  129. SrcFiles = lists:usort(lists:foldl(FSrc, [], SrcDirs)),
  130. FHrl =
  131. fun(Dir, Acc) ->
  132. esUtils:wildcard(Dir, ".*\\.hrl$") ++ Acc
  133. end,
  134. HrlFiles = lists:usort(lists:foldl(FHrl, [], HrlDirs)),
  135. Time = ?esCfgSync:getv(?srcFileTime),
  136. {keepStatus, State#state{srcFiles = SrcFiles, hrlFiles = HrlFiles}, [?gTimeout(miCollSrcFiles, Time)]};
  137. handleCast(miCompareBeams, running, #state{modules = Modules, beamTimes = BeamTimes, onsyncFun = OnsyncFun, swSyncNode = SwSyncNode} = State) ->
  138. BeamTimeList = [{Mod, LastMod} || Mod <- Modules, LastMod <- [modLastmod(Mod)], LastMod =/= 0],
  139. NewBeamLastMod = lists:usort(BeamTimeList),
  140. reloadChangedMod(BeamTimes, NewBeamLastMod, SwSyncNode, OnsyncFun, []),
  141. Time = ?esCfgSync:getv(?compareBeamTime),
  142. {keepStatus, State#state{beamTimes = NewBeamLastMod}, [?gTimeout(miCompareBeams, Time)]};
  143. handleCast(miCompareSrcFiles, running, #state{srcFiles = SrcFiles, srcFileTimes = SrcFileTimes, swSyncNode = SwSyncNode} = State) ->
  144. atomics:put(persistent_term:get(?esRecompileCnt), 1, 0),
  145. %% Create a list of file lastmod times...
  146. SrcFileTimeList = [{Src, LastMod} || Src <- SrcFiles, LastMod <- [filelib:last_modified(Src)], LastMod =/= 0],
  147. %% NewSrcFileLastMod = lists:usort(SrcFileTimeList),
  148. %% Compare to previous results, if there are changes, then recompile the file...
  149. recompileChangeSrcFile(SrcFileTimes, SrcFileTimeList, SwSyncNode),
  150. case atomics:get(persistent_term:get(?esRecompileCnt), 1) > 0 of
  151. true ->
  152. gen_ipc:cast(?SERVER, miCompareBeams);
  153. _ ->
  154. ignore
  155. end,
  156. Time = ?esCfgSync:getv(?compareSrcFileTime),
  157. {keepStatus, State#state{srcFileTimes = SrcFileTimeList}, [?gTimeout(miCompareSrcFiles, Time)]};
  158. handleCast(miCompareHrlFiles, running, #state{hrlFiles = HrlFiles, srcFiles = SrcFiles, hrlFileTimes = HrlFileTimes, swSyncNode = SwSyncNode} = State) ->
  159. atomics:put(persistent_term:get(?esRecompileCnt), 1, 0),
  160. %% Create a list of file lastmod times...
  161. HrlFileTimeList = [{Hrl, LastMod} || Hrl <- HrlFiles, LastMod <- [filelib:last_modified(Hrl)], LastMod =/= 0],
  162. %% NewHrlFileLastMod = lists:usort(HrlFileTimeList),
  163. %% Compare to previous results, if there are changes, then recompile src files that depends
  164. recompileChangeHrlFile(HrlFileTimes, HrlFileTimeList, SrcFiles, SwSyncNode),
  165. case atomics:get(persistent_term:get(?esRecompileCnt), 1) > 0 of
  166. true ->
  167. gen_ipc:cast(?SERVER, miCompareBeams);
  168. _ ->
  169. ignore
  170. end,
  171. Time = ?esCfgSync:getv(?compareSrcFileTime),
  172. {keepStatus, State#state{hrlFileTimes = HrlFileTimeList}, [?gTimeout(miCompareHrlFiles, Time)]};
  173. handleCast({miSyncNode, IsSync}, _, State) ->
  174. case IsSync of
  175. true ->
  176. {keepStatus, State#state{swSyncNode = true}};
  177. _ ->
  178. {keepStatus, State#state{swSyncNode = false}}
  179. end;
  180. handleCast(_Msg, _, _State) ->
  181. keepStatusState.
  182. handleInfo(_Msg, _, _State) ->
  183. keepStatusState.
  184. handleOnevent({gTimeout, _}, Msg, Status, State) ->
  185. handleCast(Msg, Status, State);
  186. handleOnevent(_EventType, _EventContent, _Status, _State) ->
  187. keepStatusState.
  188. terminate(_Reason, _Status, _State) ->
  189. ok.
  190. %% ***********************************PRIVATE FUNCTIONS start *******************************************
  191. addSrcDirs(DirsAndOpts) ->
  192. [
  193. begin
  194. %% ensure module out path exists & in our code path list
  195. case proplists:get_value(outdir, Opts) of
  196. undefined ->
  197. true;
  198. Path ->
  199. ok = filelib:ensure_dir(Path),
  200. true = code:add_pathz(Path)
  201. end,
  202. setOptions(Dir, Opts),
  203. Dir
  204. end || {Dir, Opts} <- DirsAndOpts
  205. ].
  206. reloadChangedMod([{Module, LastMod} | T1], [{Module, LastMod} | T2], SwSyncNode, OnsyncFun, Acc) ->
  207. reloadChangedMod(T1, T2, SwSyncNode, OnsyncFun, Acc);
  208. reloadChangedMod([{Module, _} | T1], [{Module, _} | T2], SwSyncNode, OnsyncFun, Acc) ->
  209. case code:get_object_code(Module) of
  210. error ->
  211. Msg = io_lib:format("Error loading object code for ~p", [Module]),
  212. esUtils:logErrors(Msg),
  213. reloadChangedMod(T1, T2, SwSyncNode, OnsyncFun, Acc);
  214. {Module, Binary, Filename} ->
  215. case code:load_binary(Module, Filename, Binary) of
  216. {module, Module} ->
  217. Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Success", [Module]),
  218. esUtils:logSuccess(Msg);
  219. {error, What} ->
  220. Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Errors Reason:~p", [Module, What]),
  221. esUtils:logErrors(Msg)
  222. end,
  223. case SwSyncNode of
  224. true ->
  225. {ok, NumNodes, Nodes} = syncLoadModOnAllNodes(Module),
  226. MsgNodes = io_lib:format("Reloaded(Beam changed) Mod:~s on ~p nodes:~p", [Module, NumNodes, Nodes]),
  227. esUtils:logSuccess(MsgNodes);
  228. false ->
  229. ignore
  230. end,
  231. reloadChangedMod(T1, T2, SwSyncNode, OnsyncFun, [Module | Acc])
  232. end;
  233. reloadChangedMod([{Module1, _LastMod1} | T1] = OldLastMods, [{Module2, _LastMod2} | T2] = NewLastMods, SwSyncNode, OnsyncFun, Acc) ->
  234. %% Lists are different, advance the smaller one...
  235. case Module1 < Module2 of
  236. true ->
  237. reloadChangedMod(T1, NewLastMods, SwSyncNode, OnsyncFun, Acc);
  238. false ->
  239. reloadChangedMod(OldLastMods, T2, SwSyncNode, OnsyncFun, Acc)
  240. end;
  241. reloadChangedMod(A, B, _SwSyncNode, OnsyncFun, Acc) when A =:= []; B =:= [] ->
  242. fireOnsync(OnsyncFun, Acc),
  243. ok;
  244. reloadChangedMod(undefined, _Other, _, _, _) ->
  245. ok.
  246. fireOnsync(OnsyncFun, Modules) ->
  247. case OnsyncFun of
  248. undefined -> ok;
  249. Funs when is_list(Funs) -> onsyncApplyList(Funs, Modules);
  250. Fun -> onsyncApply(Fun, Modules)
  251. end.
  252. onsyncApplyList(Funs, Modules) ->
  253. [onsyncApply(Fun, Modules) || Fun <- Funs].
  254. onsyncApply({M, F}, Modules) ->
  255. erlang:apply(M, F, [Modules]);
  256. onsyncApply(Fun, Modules) when is_function(Fun) ->
  257. Fun(Modules).
  258. getNodes() ->
  259. lists:usort(lists:flatten(nodes() ++ [rpc:call(X, erlang, nodes, []) || X <- nodes()])) -- [node()].
  260. syncLoadModOnAllNodes(Module) ->
  261. %% Get a list of nodes known by this node, plus all attached nodes.
  262. Nodes = getNodes(),
  263. NumNodes = length(Nodes),
  264. {Module, Binary, _} = code:get_object_code(Module),
  265. FSync =
  266. fun(Node) ->
  267. MsgNode = io_lib:format("Reloading '~s' on ~p", [Module, Node]),
  268. esUtils:logSuccess(MsgNode),
  269. rpc:call(Node, code, ensure_loaded, [Module]),
  270. case rpc:call(Node, code, which, [Module]) of
  271. Filename when is_binary(Filename) orelse is_list(Filename) ->
  272. %% File exists, overwrite and load into VM.
  273. ok = rpc:call(Node, file, write_file, [Filename, Binary]),
  274. rpc:call(Node, code, purge, [Module]),
  275. case rpc:call(Node, code, load_file, [Module]) of
  276. {module, Module} ->
  277. Msg = io_lib:format("Reloaded(Beam changed) Mod:~s and write Success on node:~p", [Module, Node]),
  278. esUtils:logSuccess(Msg);
  279. {error, What} ->
  280. Msg = io_lib:format("Reloaded(Beam changed) Mod:~s and write Errors on node:~p Reason:~p", [Module, Node, What]),
  281. esUtils:logErrors(Msg)
  282. end;
  283. _ ->
  284. %% File doesn't exist, just load into VM.
  285. case rpc:call(Node, code, load_binary, [Module, undefined, Binary]) of
  286. {module, Module} ->
  287. Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Success on node:~p", [Module, Node]),
  288. esUtils:logSuccess(Msg);
  289. {error, What} ->
  290. Msg = io_lib:format("Reloaded(Beam changed) Mod:~s Errors on node:~p Reason:~p", [Module, Node, What]),
  291. esUtils:logErrors(Msg)
  292. end
  293. end
  294. end,
  295. [FSync(X) || X <- Nodes],
  296. {ok, NumNodes, Nodes}.
  297. recompileChangeSrcFile([{File, LastMod} | T1], [{File, LastMod} | T2], SwSyncNode) ->
  298. recompileChangeSrcFile(T1, T2, SwSyncNode);
  299. recompileChangeSrcFile([{File, _} | T1], [{File, _} | T2], SwSyncNode) ->
  300. recompileSrcFile(File, SwSyncNode),
  301. recompileChangeSrcFile(T1, T2, SwSyncNode);
  302. recompileChangeSrcFile([{File1, _LastMod1} | T1] = OldSrcFiles, [{File2, LastMod2} | T2] = NewSrcFiles, SwSyncNode) ->
  303. %% Lists are different...
  304. case File1 < File2 of
  305. true ->
  306. %% File was removed, do nothing...
  307. recompileChangeSrcFile(T1, NewSrcFiles, SwSyncNode);
  308. false ->
  309. maybeRecompileSrcFile(File2, LastMod2, SwSyncNode),
  310. recompileChangeSrcFile(OldSrcFiles, T2, SwSyncNode)
  311. end;
  312. recompileChangeSrcFile([], [{File, LastMod} | T2], SwSyncNode) ->
  313. maybeRecompileSrcFile(File, LastMod, SwSyncNode),
  314. recompileChangeSrcFile([], T2, SwSyncNode);
  315. recompileChangeSrcFile(_A, [], _) ->
  316. %% All remaining files, if any, were removed.
  317. ok;
  318. recompileChangeSrcFile(undefined, _Other, _) ->
  319. ok.
  320. erlydtlCompile(SrcFile, Options) ->
  321. F =
  322. fun({outdir, OutDir}, Acc) -> [{out_dir, OutDir} | Acc];
  323. (OtherOption, Acc) -> [OtherOption | Acc]
  324. end,
  325. DtlOptions = lists:foldl(F, [], Options),
  326. Module = list_to_atom(lists:flatten(filename:basename(SrcFile, ".dtl") ++ "_dtl")),
  327. Compiler = erlydtl,
  328. Compiler:compile(SrcFile, Module, DtlOptions).
  329. elixir_compile(SrcFile, Options) ->
  330. Outdir = proplists:get_value(outdir, Options),
  331. Compiler = ':Elixir.Kernel.ParallelCompiler',
  332. Modules = Compiler:files_to_path([list_to_binary(SrcFile)], list_to_binary(Outdir)),
  333. Loader =
  334. fun(Module) ->
  335. Outfile = code:which(Module),
  336. Binary = file:read_file(Outfile),
  337. {Module, Binary}
  338. end,
  339. Results = lists:map(Loader, Modules),
  340. {ok, multiple, Results, []}.
  341. lfe_compile(SrcFile, Options) ->
  342. Compiler = lfe_comp,
  343. Compiler:file(SrcFile, Options).
  344. maybeRecompileSrcFile(File, LastMod, SwSyncNode) ->
  345. Module = list_to_atom(filename:basename(File, ".erl")),
  346. case code:which(Module) of
  347. BeamFile when is_list(BeamFile) ->
  348. %% check with beam file
  349. case filelib:last_modified(BeamFile) of
  350. BeamLastMod when LastMod > BeamLastMod ->
  351. recompileSrcFile(File, SwSyncNode);
  352. _ ->
  353. ok
  354. end;
  355. _ ->
  356. %% File is new, recompile...
  357. recompileSrcFile(File, SwSyncNode)
  358. end.
  359. getCompileFunAndModuleName(SrcFile) ->
  360. case esUtils:getFileType(SrcFile) of
  361. erl ->
  362. {fun compile:file/2, list_to_atom(filename:basename(SrcFile, ".erl"))};
  363. dtl ->
  364. {fun erlydtlCompile/2, list_to_atom(lists:flatten(filename:basename(SrcFile, ".dtl") ++ "_dtl"))};
  365. lfe ->
  366. {fun lfe_compile/2, list_to_atom(filename:basename(SrcFile, ".lfe"))};
  367. elixir ->
  368. {fun elixir_compile/2, list_to_atom(filename:basename(SrcFile, ".ex"))}
  369. end.
  370. getObjectCode(Module) ->
  371. case code:get_object_code(Module) of
  372. {Module, B, _Filename} -> B;
  373. _ -> undefined
  374. end.
  375. reloadIfNecessary(_CompileFun, _SrcFile, _Module, Binary, Binary, _Options) ->
  376. ok;
  377. reloadIfNecessary(CompileFun, SrcFile, Module, _OldBinary, _Binary, Options) ->
  378. %% Compiling changed the beam code. Compile and reload.
  379. CompileFun(SrcFile, Options),
  380. %% Try to load the module...
  381. case code:ensure_loaded(Module) of
  382. {module, Module} -> ok;
  383. {error, nofile} -> errorNoFile(Module);
  384. {error, embedded} ->
  385. case code:load_file(Module) of %% Module is not yet loaded, load it.
  386. {module, Module} -> ok;
  387. {error, nofile} -> errorNoFile(Module)
  388. end
  389. end,
  390. atomics:add(persistent_term:get(?esRecompileCnt), 1, 1).
  391. errorNoFile(Module) ->
  392. Msg = io_lib:format("~p Couldn't load module: nofile", [Module]),
  393. esUtils:logWarnings([Msg]).
  394. recompileSrcFile(SrcFile, SwSyncNode) ->
  395. %% Get the module, src dir, and options...
  396. case esUtils:getSrcDir(SrcFile) of
  397. {ok, SrcDir} ->
  398. {CompileFun, Module} = getCompileFunAndModuleName(SrcFile),
  399. OldBinary = getObjectCode(Module),
  400. case getOptions(SrcDir) of
  401. {ok, Options} ->
  402. case CompileFun(SrcFile, [binary, return | Options]) of
  403. {ok, Module, Binary, Warnings} ->
  404. reloadIfNecessary(CompileFun, SrcFile, Module, OldBinary, Binary, Options),
  405. printResults(Module, SrcFile, [], Warnings),
  406. {ok, [], Warnings};
  407. {ok, [{ok, Module, Binary, Warnings}], Warnings2} ->
  408. reloadIfNecessary(CompileFun, SrcFile, Module, OldBinary, Binary, Options),
  409. printResults(Module, SrcFile, [], Warnings ++ Warnings2),
  410. {ok, [], Warnings ++ Warnings2};
  411. {ok, multiple, Results, Warnings} ->
  412. [reloadIfNecessary(CompileFun, SrcFile, CompiledModule, OldBinary, Binary, Options) || {CompiledModule, Binary} <- Results],
  413. printResults(Module, SrcFile, [], Warnings),
  414. {ok, [], Warnings};
  415. {ok, OtherModule, _Binary, Warnings} ->
  416. Desc = io_lib:format("Module definition (~p) differs from expected (~s)", [OtherModule, filename:rootname(filename:basename(SrcFile))]),
  417. Errors = [{SrcFile, {0, Module, Desc}}],
  418. printResults(Module, SrcFile, Errors, Warnings),
  419. {ok, Errors, Warnings};
  420. {error, Errors, Warnings} ->
  421. printResults(Module, SrcFile, Errors, Warnings),
  422. {ok, Errors, Warnings}
  423. end;
  424. undefined ->
  425. case esUtils:tryGetModOptions(Module) of
  426. {ok, Options} ->
  427. setOptions(SrcDir, Options),
  428. recompileSrcFile(SrcFile, SwSyncNode);
  429. _ ->
  430. Msg = io_lib:format("Unable to determine options for ~s", [SrcFile]),
  431. esUtils:logErrors(Msg)
  432. end
  433. end;
  434. _ ->
  435. Msg = io_lib:format("not find the file ~s", [SrcFile]),
  436. esUtils:logErrors(Msg)
  437. end.
  438. printResults(_Module, SrcFile, [], []) ->
  439. Msg = io_lib:format("~s Recompiled", [SrcFile]),
  440. esUtils:logSuccess(lists:flatten(Msg));
  441. printResults(_Module, SrcFile, [], Warnings) ->
  442. Msg = [formatErrors(SrcFile, [], Warnings), io_lib:format("~s Recompiled with ~p warnings", [SrcFile, length(Warnings)])],
  443. esUtils:logWarnings(Msg);
  444. printResults(_Module, SrcFile, Errors, Warnings) ->
  445. Msg = [formatErrors(SrcFile, Errors, Warnings)],
  446. esUtils:logErrors(Msg).
  447. %% @private Print error messages in a pretty and user readable way.
  448. formatErrors(File, Errors, Warnings) ->
  449. AllErrors1 = lists:sort(lists:flatten([X || {_, X} <- Errors])),
  450. AllErrors2 = [{Line, "Error", Module, Description} || {Line, Module, Description} <- AllErrors1],
  451. AllWarnings1 = lists:sort(lists:flatten([X || {_, X} <- Warnings])),
  452. AllWarnings2 = [{Line, "Warning", Module, Description} || {Line, Module, Description} <- AllWarnings1],
  453. Everything = lists:sort(AllErrors2 ++ AllWarnings2),
  454. FPck =
  455. fun({Line, Prefix, Module, ErrorDescription}) ->
  456. Msg = formatError(Module, ErrorDescription),
  457. io_lib:format("~s:~p: ~s: ~s", [File, Line, Prefix, Msg])
  458. end,
  459. [FPck(X) || X <- Everything].
  460. formatError(Module, ErrorDescription) ->
  461. case erlang:function_exported(Module, format_error, 1) of
  462. true -> Module:format_error(ErrorDescription);
  463. false -> io_lib:format("~s", [ErrorDescription])
  464. end.
  465. recompileChangeHrlFile([{File, LastMod} | T1], [{File, LastMod} | T2], SrcFiles, SwSyncNode) ->
  466. recompileChangeHrlFile(T1, T2, SrcFiles, SwSyncNode);
  467. recompileChangeHrlFile([{File, _} | T1], [{File, _} | T2], SrcFiles, SwSyncNode) ->
  468. WhoInclude = whoInclude(File, SrcFiles),
  469. [recompileSrcFile(SrcFile, SwSyncNode) || SrcFile <- WhoInclude],
  470. recompileChangeHrlFile(T1, T2, SrcFiles, SwSyncNode);
  471. recompileChangeHrlFile([{File1, _LastMod1} | T1] = OldHrlFiles, [{File2, LastMod2} | T2] = NewHrlFiles, SrcFiles, SwSyncNode) ->
  472. %% Lists are different...
  473. case File1 < File2 of
  474. true ->
  475. %% File was removed, do nothing...
  476. warnDelHrlFiles(File1, SrcFiles),
  477. recompileChangeHrlFile(T1, NewHrlFiles, SrcFiles, SwSyncNode);
  478. false ->
  479. %% File is new, look for src that include it
  480. WhoInclude = whoInclude(File2, SrcFiles),
  481. [maybeRecompileSrcFile(SrcFile, LastMod2, SwSyncNode) || SrcFile <- WhoInclude],
  482. recompileChangeHrlFile(OldHrlFiles, T2, SrcFiles, SwSyncNode)
  483. end;
  484. recompileChangeHrlFile([], [{File, LastMod} | T2], SrcFiles, SwSyncNode) ->
  485. WhoInclude = whoInclude(File, SrcFiles),
  486. [maybeRecompileSrcFile(SrcFile, LastMod, SwSyncNode) || SrcFile <- WhoInclude],
  487. recompileChangeHrlFile([], T2, SrcFiles, SwSyncNode);
  488. recompileChangeHrlFile([{File1, _LastMod1} | T1], [], SrcFiles, SwSyncNode) ->
  489. warnDelHrlFiles(File1, SrcFiles),
  490. recompileChangeHrlFile(T1, [], SrcFiles, SwSyncNode);
  491. recompileChangeHrlFile([], [], _, _) ->
  492. %% Done
  493. ok;
  494. recompileChangeHrlFile(undefined, _Other, _, _) ->
  495. %% First load, do nothing
  496. ok.
  497. warnDelHrlFiles(HrlFile, SrcFiles) ->
  498. WhoInclude = whoInclude(HrlFile, SrcFiles),
  499. case WhoInclude of
  500. [] -> ok;
  501. _ ->
  502. Msg = io_lib:format("Warning. Deleted ~p file included in existing src files: ~p", [filename:basename(HrlFile), lists:map(fun(File) ->
  503. filename:basename(File) end, WhoInclude)]),
  504. esUtils:logSuccess(lists:flatten(Msg))
  505. end.
  506. whoInclude(HrlFile, SrcFiles) ->
  507. HrlFileBaseName = filename:basename(HrlFile),
  508. Pred =
  509. fun(SrcFile) ->
  510. {ok, Forms} = epp_dodger:parse_file(SrcFile),
  511. isInclude(HrlFileBaseName, Forms)
  512. end,
  513. lists:filter(Pred, SrcFiles).
  514. isInclude(_HrlFile, []) ->
  515. false;
  516. isInclude(HrlFile, [{tree, attribute, _, {attribute, _, [{_, _, IncludeFile}]}} | Forms]) when is_list(IncludeFile) ->
  517. IncludeFileBaseName = filename:basename(IncludeFile),
  518. case IncludeFileBaseName of
  519. HrlFile -> true;
  520. _ -> isInclude(HrlFile, Forms)
  521. end;
  522. isInclude(HrlFile, [_SomeForm | Forms]) ->
  523. isInclude(HrlFile, Forms).
  524. filterCollMods(Modules) ->
  525. excludeMods(onlyMods(Modules)).
  526. onlyMods(Modules) ->
  527. case ?esCfgSync:getv(?onlyMods) of
  528. [] ->
  529. Modules;
  530. OnlyMods ->
  531. [Mod || Mod <- Modules, checkModIsMatch(OnlyMods, Mod) == true]
  532. end.
  533. excludeMods(Modules) ->
  534. case ?esCfgSync:getv(?excludedMods) of
  535. [] ->
  536. Modules;
  537. ExcludedModules ->
  538. [Mod || Mod <- Modules, checkModIsMatch(ExcludedModules, Mod) == false]
  539. end.
  540. checkModIsMatch([], _Module) ->
  541. false;
  542. checkModIsMatch([ModOrPattern | T], Module) ->
  543. case ModOrPattern of
  544. Module ->
  545. true;
  546. _ when is_list(ModOrPattern) ->
  547. case re:run(atom_to_list(Module), ModOrPattern) of
  548. {match, _} ->
  549. true;
  550. nomatch ->
  551. checkModIsMatch(T, Module)
  552. end;
  553. _ ->
  554. checkModIsMatch(T, Module)
  555. end.
  556. collSrcDirs(Modules, AddDirs, OnlyDirs) ->
  557. FColl =
  558. fun
  559. (Mod, {SrcAcc, HrlAcc} = Acc) ->
  560. case esUtils:getModSrcDir(Mod) of
  561. {ok, SrcDir} ->
  562. case isOnlyDir(OnlyDirs, SrcDir) of
  563. true ->
  564. {ok, Options} = esUtils:getModOptions(Mod),
  565. HrlDir = proplists:get_all_values(i, Options),
  566. setOptions(SrcDir, Options),
  567. {[SrcDir | SrcAcc], HrlDir ++ HrlAcc};
  568. _ ->
  569. Acc
  570. end;
  571. undefined ->
  572. Acc
  573. end
  574. end,
  575. {SrcDirs, HrlDirs} = lists:foldl(FColl, {AddDirs, []}, Modules),
  576. USortedSrcDirs = lists:usort(SrcDirs),
  577. USortedHrlDirs = lists:usort(HrlDirs),
  578. {USortedSrcDirs, USortedHrlDirs}.
  579. isOnlyDir([], _) ->
  580. true;
  581. isOnlyDir(ReplaceDirs, SrcDir) ->
  582. isMatchDir(ReplaceDirs, SrcDir).
  583. isMatchDir([], _SrcDir) ->
  584. false;
  585. isMatchDir([SrcDir | _ReplaceDirs], SrcDir) ->
  586. true;
  587. isMatchDir([OneDir | ReplaceDirs], SrcDir) ->
  588. case re:run(SrcDir, OneDir) of
  589. nomatch -> isMatchDir(ReplaceDirs, SrcDir);
  590. _ -> true
  591. end.
  592. modLastmod(Mod) ->
  593. case code:which(Mod) of
  594. Beam when is_list(Beam) ->
  595. filelib:last_modified(Beam);
  596. _Other ->
  597. 0 %% non_existing | cover_compiled | preloaded
  598. end.
  599. getOptions(SrcDir) ->
  600. case erlang:get(SrcDir) of
  601. undefined ->
  602. undefined;
  603. Options ->
  604. {ok, Options}
  605. end.
  606. setOptions(SrcDir, Options) ->
  607. case erlang:get(SrcDir) of
  608. undefined ->
  609. erlang:put(SrcDir, Options);
  610. OldOptions ->
  611. NewOptions =
  612. case lists:keytake(compile_info, 1, Options) of
  613. {value, {compile_info, ValList1}, Options1} ->
  614. case lists:keytake(compile_info, 1, OldOptions) of
  615. {value, {compile_info, ValList2}, Options2} ->
  616. [{compile_info, lists:usort(ValList1 ++ ValList2)} | lists:usort(Options1 ++ Options2)];
  617. _ ->
  618. lists:usort(Options ++ OldOptions)
  619. end;
  620. _ ->
  621. lists:usort(Options ++ OldOptions)
  622. end,
  623. erlang:put(SrcDir, NewOptions)
  624. end.
  625. loadCfg() ->
  626. KVs = [{Key, esUtils:getEnv(Key, DefVal)} || {Key, DefVal} <- ?CfgList],
  627. esUtils:load(?esCfgSync, KVs).
  628. %% ***********************************PRIVATE FUNCTIONS end *********************************************