aboutsummaryrefslogtreecommitdiff
path: root/vim/bundle/syntastic/syntax_checkers/erlang/erlang_check_file.erl
blob: 730e60053d451311e96df85f7201cbbbfd73085e (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
#!/usr/bin/env escript

main([File]) ->
    Dir = get_root(filename:dirname(File)),
    Defs = [strong_validation,
            warn_export_all,
            warn_export_vars,
            warn_shadow_vars,
            warn_obsolete_guard,
            warn_unused_import,
            report,
            {i, Dir ++ "/include"}],
    %% `rebar.config` is looked for,
    %% but it is not necessarily the one in the project root.
    %% I.e. it may be one deeper in the project file hierarchy.
    RebarFile = rebar_file(Dir),
    %% `rebar.config` might contain relative paths.
    %% They are relative to the file! Not to the project root.
    RebarOpts = rebar_opts(Dir ++ "/" ++ RebarFile),
    code:add_patha(filename:absname("ebin")),
    %% `compile:file/2` requires the `{i, Path}` to be relative
    %% to CWD - no surprise here.
    compile:file(File, Defs ++ translate_paths(Dir, RebarOpts));

main(_) ->
    io:format("Usage: ~s <file>~n", [escript:script_name()]),
    halt(1).

rebar_file(Dir) ->
    DirList = filename:split(Dir),
    case lists:last(DirList) of
        "test" ->
            "rebar.test.config";
        _ ->
            "rebar.config"
    end.

rebar_opts(RebarFile) ->
    Dir = get_root(filename:dirname(RebarFile)),
    case file:consult(RebarFile) of
        {ok, Terms} ->
            RebarLibDirs = proplists:get_value(lib_dirs, Terms, []),
            lists:foreach(
                fun(LibDir) ->
                        code:add_pathsa(filelib:wildcard(LibDir ++ "/*/ebin"))
                end, RebarLibDirs),
            RebarDepsDir = proplists:get_value(deps_dir, Terms, "deps"),
            code:add_pathsa(filelib:wildcard(RebarDepsDir ++ "/*/ebin")),
            IncludeDeps = {i, filename:join(Dir, RebarDepsDir)},
            proplists:get_value(erl_opts, Terms, []) ++ [IncludeDeps];
        {error, _} when RebarFile == "rebar.config" ->
          fallback_opts();
        {error, _} ->
            rebar_opts("rebar.config")
    end.

fallback_opts() ->
    code:add_pathsa(filelib:wildcard("deps/*/ebin")),
    code:add_pathsa(nested_app_ebins()),
    [
     { i, filename:absname("apps") }, { i, filename:absname("deps") } | [ { i, filename:absname(Path) } || Path <- filelib:wildcard("deps/*/apps")]
    ].

nested_app_ebins() ->
    DetectedAppSrcFiles = filelib:wildcard("deps/*/apps/**/*.app.src"),
    [apps_dir_from_src(AppSrcFile)||AppSrcFile<-DetectedAppSrcFiles].

apps_dir_from_src(SrcFile) ->
    SrcDir = filename:dirname(SrcFile),
    filename:join(SrcDir, "../../ebin").

get_root(Dir) ->
    Path = filename:split(filename:absname(Dir)),
    filename:join(get_root(lists:reverse(Path), Path)).

get_root([], Path) ->
    Path;
get_root(["src" | Tail], _Path) ->
    lists:reverse(Tail);
get_root(["test" | Tail], _Path) ->
    lists:reverse(Tail);
get_root([_ | Tail], Path) ->
    get_root(Tail, Path).

translate_paths(Dir, RebarOpts) ->
    [ translate_path(Dir, Opt) || Opt <- RebarOpts ].

translate_path(Dir, {i, Path}) ->
    case Path of
        %% absolute
        "/" ++ _ -> {i, Path};
        %% relative -> make absolute taking rebar.config location into account
        _ -> {i, filename:join([Dir, Path])}
    end;
translate_path(_, Other) -> Other.