11defmodule Mix.Tasks.Compile.Erlang do
2+
3+ alias :epp , as: Epp
4+ alias :digraph , as: Graph
5+ alias :digraph_utils , as: GraphUtils
6+ alias :code , as: Code
7+ alias :compile , as: Compiler
8+ alias Mix.Utils
29 use Mix.Task
310
411 @ hidden true
@@ -7,57 +14,175 @@ defmodule Mix.Tasks.Compile.Erlang do
714 @ moduledoc """
815 A task to compile Erlang source files.
916
17+ When this task runs, it will first check the mod times of
18+ all of the files. Every file will checked, if file or
19+ file dependencies, like include files, was changed.
20+ If file of his dependencies haven't been changed since the
21+ last compilation, it will not compile. If file or one of his
22+ dependency has changed, it will compile.
23+
24+ For this reason, this task touches your `:compile_path`
25+ directory and sets the modification time to the current
26+ time and date at the end of each compilation. You can
27+ force compilation regardless of mod times by passing
28+ the `--force` option.
29+
1030 ## Command line options
1131
32+ * `--force` - forces compilation regardless of module times;
33+
34+ ## Configuration
35+
1236 * `ERL_COMPILER_OPTIONS` - can be used to give default compile options.
1337 It's value must be a valid Erlang term. If the value is a list, it will
1438 be used as is. If it is not a list, it will be put into a list.
1539
16- ## Configuration
40+ * `:erlc_paths` - directories to find source files.
41+ Defaults to `["src"]`, can be configured as:
42+
43+ [erlc_paths: ["src", "other"]]
44+
45+ * `:erlc_include_path` - directory for adding include files.
46+ Defaults to `"include"`, can be configured as:
47+
48+ [`erlc_include_path`: "other"]
49+
50+ * `:erlc_options` - compilation options that applies
51+ to Erlang's compiler.
52+ This options are setted:
1753
18- * `:erlc_options` - compilation options that applies to Erlang compiler
19- By default, the following options are on: `[:verbose, :report_errors, :report_warnings]`
54+ :outdir to a configured :compile_path
55+ :i to a configured :include_path
56+ :report
57+
58+ and :debug_info in project configuration
59+
60+ There are many other available options here:
61+ http://www.erlang.org/doc/man/compile.html#file-2
2062
2163 """
22- def run ( _ ) do
64+
65+ defrecord Erl , file: nil , module: nil , behaviours: [ ] , compile: [ ] ,
66+ includes: [ ] , mtime: nil , invalid: false
67+
68+ def run ( args ) do
69+ { opts , _ } = OptionParser . parse ( args , switches: [ force: :boolean ] )
70+
2371 project = Mix . project
72+ source_paths = project [ :erlc_paths ]
73+ files = Mix.Utils . extract_files ( source_paths , [ :erl ] )
74+ compile_path = to_erl_file project [ :compile_path ]
75+ include_path = to_erl_file project [ :erlc_include_path ]
76+
77+ erlc_options = [ { :outdir , compile_path } , { :i , include_path } , :report
78+ | project [ :erlc_options ] || [ ] ]
79+ erlc_options = Enum . map erlc_options , fn ( opt ) ->
80+ case opt do
81+ { :i , dir } -> { :i , to_erl_file ( dir ) }
82+ _ -> opt
83+ end
84+ end
2485
25- files = Mix.Utils . extract_files ( project [ :erlc_paths ] , [ :erl ] )
26- compile_path = project [ :compile_path ]
86+ files = files |> scan_sources ( include_path , source_paths ) |> sort_dependency
87+ unless opts [ :force ] , do: files = Enum . filter ( files , check_file ( compile_path , & 1 ) )
2788
2889 if files == [ ] do
2990 :noop
3091 else
31- Mix. Utils. preserving_mtime ( compile_path , fn ->
92+ Utils . preserving_mtime ( compile_path , fn ->
3293 File . mkdir_p! compile_path
33- compile_files project , files , compile_path
94+ compile_files files , compile_path , erlc_options
3495 end )
3596
3697 :ok
3798 end
3899 end
39100
40- defp compile_files ( project , files , compile_path ) do
41- erlc_options = project [ :erlc_options ] || [ ]
101+ defp scan_sources ( files , include_path , source_paths ) do
102+ include_pathes = [ include_path | source_paths ]
103+ List . foldl ( files , [ ] , fn ( file , acc ) -> scan_source ( acc , file , include_pathes ) end ) |> Enum . reverse
104+ end
42105
43- erlc_options = Enum . map erlc_options , fn ( opt ) ->
44- case opt do
45- { :i , dir } -> { :i , Path . expand ( dir ) |> binary_to_list }
46- _ -> opt
106+ defp scan_source ( acc , file , include_pathes ) do
107+ erl_file = Erl [ mtime : Utils . last_modified ( file ) ,
108+ file: file ,
109+ module: Path . basename ( file , ".erl" ) ]
110+ case Epp . parse_file ( to_erl_file ( file ) , include_pathes , [ ] ) do
111+ { :ok , forms } ->
112+ [ List . foldl ( tl ( forms ) , erl_file , fn ( f , acc ) -> do_form ( file , f , acc ) end ) | acc ]
113+ { :error , _error } ->
114+ acc
115+ end
116+ end
117+
118+ defp do_form ( file , form , erl ) do
119+ case form do
120+ { :attribute , _ , :file , { include_file , _ } } when file != include_file ->
121+ erl . update ( includes: [ include_file | erl . includes ] )
122+ { :attribute , _ , :behaviour , behaviour } ->
123+ erl . update ( behaviour: [ behaviour | erl . behaviours ] )
124+ { :attribute , _ , :compile , value } ->
125+ erl . update ( compile: [ value | erl . compile ] )
126+ _ ->
127+ erl
128+ end
129+ end
130+
131+ defp sort_dependency ( erls ) do
132+ graph = Graph . new
133+ lc erl inlist erls do
134+ Graph . add_vertex ( graph , erl . module , erl )
135+ end
136+ lc erl inlist erls do
137+ lc b inlist erl . behaviours , do: Graph . add_edge ( graph , b , erl . module )
138+ lc a inlist erl . compile do
139+ case a do
140+ { :parse_transform , transform } -> Graph . add_edge ( graph , transform , erl . module ) ;
141+ _ -> :ok
142+ end
47143 end
48144 end
145+ result =
146+ case GraphUtils . topsort ( graph ) do
147+ :false -> erls ;
148+ mods ->
149+ lc m inlist mods , do: elem ( Graph . vertex ( graph , m ) , 1 )
150+ end
151+ Graph . delete ( graph )
152+ result
153+ end
154+
155+ defp check_file ( compile_path , erl ) do
156+ beam = Path . join ( compile_path , "#{ erl . module } #{ Code . objfile_extension } " )
157+ case File . regular? ( beam ) do
158+ :false -> :true
159+ :true ->
160+ beammtime = Utils . last_modified ( beam )
161+ ( beammtime <= erl . mtime ) or Utils . check_mtime ( beammtime , erl . includes )
162+ end
163+ end
49164
50- compile_path = compile_path |> Path . expand |> binary_to_list
51- erlc_options = [ { :outdir , compile_path } ] ++ erlc_options
165+ defp compile_files ( files , compile_path , erlc_options ) do
52166 File . mkdir_p! ( compile_path )
167+ Enum . each files , compile_file ( & 1 , erlc_options )
168+ end
53169
54- Enum . each files , fn ( file ) ->
55- file = Path . rootname ( file , ".erl" ) |> Path . expand |> binary_to_list
170+ defp compile_file ( erl , erlc_options ) do
171+ file = to_erl_file Path . rootname ( erl . file , ".erl" )
172+ interpret_result file , :compile . file ( file , erlc_options ) , ".erl"
173+ end
56174
57- case :compile . file ( file , erlc_options ) do
58- { :ok , _ } -> Mix . shell . info "Compiled #{ file } .erl"
59- :error -> Mix . shell . error "== Compilation error on file #{ file } .erl =="
60- end
175+ def interpret_result ( file , result , ext // "" ) do
176+ case result do
177+ { :ok , _ } ->
178+ Mix . shell . info "Compiled #{ file } #{ ext } "
179+ :error ->
180+ :ok
61181 end
62182 end
183+
184+ def to_erl_file file do
185+ to_char_list ( file )
186+ end
187+
63188end
0 commit comments