Browse Source

working mad ling

Namdak Tonpa 10 years ago
parent
commit
78713a89d4
4 changed files with 28 additions and 29 deletions
  1. 1 1
      include/mad.hrl
  2. BIN
      mad
  3. 1 1
      rebar.config
  4. 26 27
      src/mad_ling.erl

+ 1 - 1
include/mad.hrl

@@ -1 +1 @@
--define(VERSION,"105aa6").
+-define(VERSION,"c5dc3f").

BIN
mad


+ 1 - 1
rebar.config

@@ -1,4 +1,4 @@
 {sub_dirs,["deps/ling/apps"]}.
 {deps_dir,"deps"}.
-{deps, [{ling, ".*", {git, "git://github.com/cloudozer/ling", {tag, "master"}}},
+{deps, [{ling, ".*", {git, "git://github.com/proger/ling", {tag, "osx-again"}}},
         {sh, ".*",   {git, "git://github.com/synrc/sh",       {tag, "1.4"}}}]}.

+ 26 - 27
src/mad_ling.erl

@@ -1,16 +1,17 @@
 -module(mad_ling).
+-author('Maxim Sokhatsky').
 -description("LING Erlang Virtual Machine Bundle Packaging").
 -copyright('Cloudozer, LLP').
 -compile(export_all).
 -define(ARCH, list_to_atom( case os:getenv("ARCH") of false -> "posix_x86"; A -> A end)).
 
 main(App) ->
-    io:format("ARCH: ~p~n",[?ARCH]),
-    io:format("Bundle Name: ~p~n",[mad_repl:local_app()]),
-    io:format("System: ~p~n",     [mad_repl:system()]),
-    io:format("Apps: ~p~n",       [mad_repl:applist()]),
-    io:format("Overlay: ~p~n",    [[{filename:basename(N),size(B)}||{N,B}<-mad_bundle:overlay()]]),
-    io:format("Files: ~p~n",      [[B||{B,_} <- bundle()]]),
+    io:format("ARCH: ~p~n",         [?ARCH]),
+    io:format("Bundle Name: ~p~n",  [mad_repl:local_app()]),
+    io:format("System: ~p~n",       [mad_repl:system()]),
+    io:format("Apps: ~p~n",         [mad_repl:applist()]),
+    io:format("Overlay: ~p~n",      [[{filename:basename(N),size(B)}||{N,B} <- mad_bundle:overlay()]]),
+    io:format("Files: ~p~n",        [[{filename:basename(N),size(B)}||{N,B} <- bundle()]]),
     add_apps(),
     false.
 
@@ -27,37 +28,34 @@ library(Filename) -> case filename:split(Filename) of
                                _ -> mad_repl:local_app() end.
 
 apps(Ordered) ->
-    Overlay = [{filename:basename(N),B}||{N,B}<-mad_bundle:overlay()],
+    Overlay = [ {filename:basename(N),B} || {N,B} <- mad_bundle:overlay() ],
     lists:foldl(fun({N,B},Acc) ->
         A = library(N),
         Base = filename:basename(N),
         Body = case lists:keyfind(Base,1,Overlay) of
                     false -> B;
-                    {Base,Bin} -> io:format("Overlay: ~p~n",[{A,Base}]), Bin end,
+                    {Base,Bin} -> 'overlay', Bin end,
          case lists:keyfind(A,1,Acc) of
               false -> [{A,[{A,Base,Body}]}|Acc];
               {A,Files} -> lists:keyreplace(A,1,Acc,{A,[{A,Base,Body}|Files]}) end
     end,lists:zip(Ordered,lists:duplicate(length(Ordered),[])),bundle()).
 
-boot(Ordered) ->
-    {script,Erlang,List} = binary_to_term(element(2,file:read_file(lists:concat([code:root_dir(),"/bin/start.boot"])))),
-    Boot = [ L || L<-List, element(1,L) /= 'apply', L/={'progress',started} ]
-        ++ [{'apply',{application,start_boot,[A,permanent]}} || A <- Ordered ]
-        ++ [{'progress',synrc}],
-    io:format("Boot File: ~p~n",[Boot]),
-    {[],"start.boot",term_to_binary({script,Erlang,List})}.
+lib({App,Files}) ->
+   { App, lists:concat(["/erlang/lib/",App,"/ebin"]), Files }.
 
-erlang_lib({App,Files}) -> {App,lists:concat(["/erlang/lib/",App,"/ebin"]),Files}.
+boot(Ordered) ->
+   BootCode = element(2,file:read_file(lists:concat([code:root_dir(),"/bin/start.boot"]))),
+   { script, Erlang, Boot } = binary_to_term(BootCode),
+   AutoLaunch = {script,Erlang,Boot++[{apply,{application,start,[App]}} || App <- Ordered]},
+   { boot, "start.boot", term_to_binary(AutoLaunch) }.
 
 add_apps() ->
     {ok,Ordered} = mad_plan:orderapps(),
-    Bucks     = [ {boot, "/boot", [local_map, boot(Ordered)]} ] ++
-                [ erlang_lib(E) || E <- apps(Ordered) ],
+    Bucks = [{boot,"/boot",[local_map, boot(Ordered)]}] ++ [ lib(E) || E <- apps(Ordered) ],
     io:format("Bucks: ~p~n",[[{App,Mount,[{filename:basename(F),size(Bin)}||{_,F,Bin}<-Files]}||{App,Mount,Files}<-Bucks]]),
-    EmbedFsPath   = lists:concat([cache_dir(),"/embed.fs"]),
-    io:format("Initializing EMBED.FS: ..."),
+    EmbedFsPath = lists:concat([cache_dir(),"/embed.fs"]),
+    io:format("Initializing EMBED.FS:"),
     Res = embed_fs(EmbedFsPath,Bucks),
-    io:format("~p~n",[Res]),
 	{ok, EmbedFsObject} = embedfs_object(EmbedFsPath),
 	Res = case sh:oneliner(ld() ++
 	           ["vmling.o", EmbedFsObject, "-o", "../" ++ atom_to_list(mad_repl:local_app()) ++ ".img"],
@@ -78,16 +76,18 @@ embed_fs(EmbedFsPath,Bucks)  ->
           BuckBinCount = length(Bins),
           file:write(EmbedFs, <<BuckNameSize, BuckName/binary, BuckBinCount:32>>),
           lists:foreach(fun
-                    (local_map) -> write_bin(EmbedFs, [], "local.map", local_map(Bucks));
-                  ({App,F,Bin}) -> write_bin(EmbedFs, App, filename:basename(F), Bin)
+                    (local_map) -> LocalMap = local_map(Bucks),
+                                   io:format("~nMount View:~n ~s",[LocalMap]),
+                                   write_bin(EmbedFs, "local.map", LocalMap);
+                  ({App,F,Bin}) -> write_bin(EmbedFs, filename:basename(F), Bin)
           end,Bins)
     end,Bucks),
     file:close(EmbedFs),
 	ok.
 
 embedfs_object(EmbedFsPath) ->
-	EmbedCPath = filename:join(filename:absname(cache_dir()), "embedfs.c"),
-	OutPath = filename:join(filename:absname(cache_dir()), "embedfs.o"),
+	EmbedCPath  = filename:join(filename:absname(cache_dir()), "embedfs.c"),
+	OutPath     = filename:join(filename:absname(cache_dir()), "embedfs.o"),
 	{ok, Embed} = file:read_file(EmbedFsPath),
 	io:format("Creating EMBED.FS C file: ..."),
 	Res = bfd_objcopy:blob_to_src(EmbedCPath, "_binary_embed_fs", Embed),
@@ -99,14 +99,13 @@ embedfs_object(EmbedFsPath) ->
 	io:format("~p~n",[Res]),
 	{ok, OutPath}.
 
-write_bin(Dev, App, F, Bin) ->
+write_bin(Dev, F, Bin) ->
     {ListName,Data} = case filename:extension(F) of
         ".beam" ->  { filename:rootname(F) ++ ".ling", beam_to_ling(Bin) };
               _ ->  { F, Bin } end,
     Name = binary:list_to_bin(ListName),
     NameSize = size(Name),
     DataSize = size(Data),
-    io:format("Write: ~p ~p~n",[Name,DataSize]),
     file:write(Dev, <<NameSize, Name/binary, DataSize:32, Data/binary>>).
 
 beam_to_ling(B) ->