mad_ling.erl 6.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137
  1. -module(mad_ling).
  2. -author('Maxim Sokhatsky').
  3. -description("LING Erlang Virtual Machine Bundle Packaging").
  4. -copyright('Cloudozer, LLP').
  5. -compile(export_all).
  6. -define(ARCH, list_to_atom( case os:getenv("ARCH") of false -> "posix"; A -> A end)).
  7. main(_App) ->
  8. io:format("ARCH: ~p~n", [?ARCH]),
  9. io:format("Bundle Name: ~p~n", [mad_repl:local_app()]),
  10. io:format("System: ~p~n", [mad_repl:system()]),
  11. io:format("Apps: ~p~n", [mad_repl:applist()]),
  12. % io:format("Overlay: ~p~n", [[{filename:basename(N),size(B)}||{N,B} <- mad_bundle:overlay()]]),
  13. % io:format("Files: ~p~n", [[{filename:basename(N),size(B)}||{N,B} <- bundle()]]),
  14. io:format("Overlay: ~p~n", [[filename:basename(N)||{N,_B} <- mad_bundle:overlay()]]),
  15. add_apps(),
  16. false.
  17. cache_dir() -> ".madaline/".
  18. local_map(Bucks) -> list_to_binary(lists:map(fun({B,M,_}) -> io_lib:format("~s /~s\n",[M,B]) end,Bucks)).
  19. bundle() -> lists:flatten([ mad_bundle:X() || X <- [beams,privs,system_files,overlay] ]).
  20. library(Filename) -> case filename:split(Filename) of
  21. ["deps","ling","apps",Lib|_] -> list_to_atom(Lib);
  22. ["ebin"|_] -> mad_repl:local_app();
  23. ["priv"|_] -> mad_repl:local_app();
  24. A when length(A) >= 3 -> list_to_atom(hd(string:tokens(lists:nth(3,lists:reverse(A)),"-")));
  25. ["apps",Lib|_] -> list_to_atom(Lib);
  26. ["deps",Lib|_] -> list_to_atom(Lib);
  27. _ -> mad_repl:local_app() end.
  28. apps(Ordered) ->
  29. Overlay = [ {filename:basename(N),B} || {N,B} <- mad_bundle:overlay() ],
  30. lists:foldl(fun({N,B},Acc) ->
  31. A = library(N),
  32. Base = filename:basename(N),
  33. Body = case lists:keyfind(Base,1,Overlay) of
  34. false -> B;
  35. {Base,Bin} -> 'overlay', Bin end,
  36. case lists:keyfind(A,1,Acc) of
  37. false -> [{A,[{A,Base,Body}]}|Acc];
  38. {A,Files} -> lists:keyreplace(A,1,Acc,{A,[{A,Base,Body}|Files]}) end
  39. end,lists:zip(Ordered,lists:duplicate(length(Ordered),[])),bundle()).
  40. lib({App,Files}) ->
  41. { App, lists:concat(["/erlang/lib/",App,"/ebin"]), Files }.
  42. boot(Ordered) ->
  43. BootCode = element(2,file:read_file(lists:concat([code:root_dir(),"/bin/start.boot"]))),
  44. { script, Erlang, Boot } = binary_to_term(BootCode),
  45. AutoLaunch = {script,Erlang,Boot++[{apply,{application,start,[App]}} || App <- Ordered]},
  46. io:format("Boot Code: ~p~n",[AutoLaunch]),
  47. { boot, "start.boot", term_to_binary(AutoLaunch) }.
  48. add_apps() ->
  49. {ok,Ordered} = mad_plan:orderapps(),
  50. Bucks = [{boot,"/boot",[local_map, boot(Ordered)]}] ++ [ lib(E) || E <- apps(Ordered) ],
  51. %io:format("Bucks: ~p~n",[[{App,Mount,[{filename:basename(F),size(Bin)}||{_,F,Bin}<-Files]}||{App,Mount,Files}<-Bucks]]),
  52. io:format("Bucks: ~p~n",[[{App,Mount,length(Files)}||{App,Mount,Files}<-Bucks]]),
  53. filelib:ensure_dir(cache_dir()),
  54. EmbedFsPath = lists:concat([cache_dir(),"/embed.fs"]),
  55. io:format("Initializing EMBED.FS:"),
  56. Res = embed_fs(EmbedFsPath,Bucks),
  57. {ok, EmbedFsObject} = embedfs_object(EmbedFsPath),
  58. Oneliner = ld() ++
  59. ["../deps/ling/core/vmling.o"] ++
  60. ["-lm", "-lpthread", "-ldl"] ++
  61. [EmbedFsObject, "-o", "../" ++ atom_to_list(mad_repl:local_app()) ++ ".img"],
  62. io:format("LD: ~p~n",[Oneliner]),
  63. Res = case sh:oneliner(Oneliner,cache_dir()) of
  64. {_,0,_} -> ok;
  65. {_,_,M} -> binary_to_list(M) end,
  66. io:format("Linking Image: ~p~n",[Res]).
  67. embed_fs(EmbedFsPath,Bucks) ->
  68. {ok, EmbedFs} = file:open(EmbedFsPath, [write]),
  69. BuckCount = length(Bucks),
  70. BinCount = lists:foldl(fun({_,_,Bins},Count) -> Count + length(Bins) end,0,Bucks),
  71. file:write(EmbedFs, <<BuckCount:32>>),
  72. file:write(EmbedFs, <<BinCount:32>>),
  73. lists:foreach(fun({Buck,_,Bins}) ->
  74. BuckName = binary:list_to_bin(atom_to_list(Buck)),
  75. BuckNameSize = size(BuckName),
  76. BuckBinCount = length(Bins),
  77. file:write(EmbedFs, <<BuckNameSize, BuckName/binary, BuckBinCount:32>>),
  78. lists:foreach(fun
  79. (local_map) -> LocalMap = local_map(Bucks),
  80. io:format("~nMount View:~n ~s",[LocalMap]),
  81. write_bin(EmbedFs, "local.map", LocalMap);
  82. ({_App,F,Bin}) -> write_bin(EmbedFs, filename:basename(F), Bin)
  83. end,Bins)
  84. end,Bucks),
  85. file:close(EmbedFs),
  86. ok.
  87. embedfs_object(EmbedFsPath) ->
  88. EmbedCPath = filename:join(filename:absname(cache_dir()), "embedfs.c"),
  89. OutPath = filename:join(filename:absname(cache_dir()), "embedfs.o"),
  90. {ok, Embed} = file:read_file(EmbedFsPath),
  91. io:format("Creating EMBED.FS C file: ..."),
  92. Res = bfd_objcopy:blob_to_src(EmbedCPath, "_binary_embed_fs", Embed),
  93. io:format("~p~n",[Res]),
  94. io:format("Compilation of Filesystem object: ..."),
  95. Res = case sh:oneliner(cc() ++ ["-o", OutPath, "-c", EmbedCPath]) of
  96. {_,0,_} -> ok;
  97. {_,_,M} -> binary_to_list(M) end,
  98. io:format("~p~n",[Res]),
  99. io:format("Out Path: ~p~n",[OutPath]),
  100. {ok, OutPath}.
  101. write_bin(Dev, F, Bin) ->
  102. {ListName,Data} = case filename:extension(F) of
  103. ".beam" -> { filename:rootname(F) ++ ".ling", beam_to_ling(Bin) };
  104. _ -> { F, Bin } end,
  105. Name = binary:list_to_bin(ListName),
  106. NameSize = size(Name),
  107. DataSize = size(Data),
  108. file:write(Dev, <<NameSize, Name/binary, DataSize:32, Data/binary>>).
  109. beam_to_ling(B) ->
  110. ling_lib:specs_to_binary(element(2,ling_code:ling_to_specs(element(2,ling_code:beam_to_ling(B))))).
  111. gold() -> gold("ld").
  112. gold(Prog) -> [Prog, "-T", "ling.lds", "-nostdlib"].
  113. ld() -> ld(?ARCH).
  114. ld(arm) -> gold("arm-none-eabi-ld");
  115. ld(xen_x86) -> case os:type() of {unix, darwin} -> ["x86_64-pc-linux-ld"]; _ -> gold() end;
  116. ld(posix) -> case os:type() of {unix, darwin} ->
  117. ["clang","-image_base","0x8000","-pagezero_size","0x8000","-arch","x86_64"];
  118. _ -> gold() end;
  119. ld(_) -> gold().
  120. cc() -> cc(?ARCH).
  121. cc(arm) -> ["arm-none-eabi-gcc", "-mfpu=vfp", "-mfloat-abi=hard"];
  122. cc(xen_x86) -> case os:type() of {unix, darwin} -> ["x86_64-pc-linux-gcc"]; _ -> ["cc"] end;
  123. cc(_) -> ["cc"].