@@ -93,6 +93,57 @@ let libs_and_ppx_under_dir sctx ~db ~dir =
93
93
, pps )
94
94
else
95
95
(acc, pps))
96
+ | Dune_file. Executables exes -> (
97
+ let * libs =
98
+ let open Memo.Build.O in
99
+ let * compile_info =
100
+ let project = Scope. project d.scope in
101
+ let dune_version = Dune_project. dune_version project in
102
+ let + pps =
103
+ Resolve.Build. read_memo_build
104
+ (Preprocess.Per_module. with_instrumentation
105
+ exes.buildable.preprocess
106
+ ~instrumentation_backend:
107
+ (Lib.DB. instrumentation_backend (Scope. libs d.scope)))
108
+ >> | Preprocess.Per_module. pps in
109
+ Lib.DB. resolve_user_written_deps_for_exes
110
+ db exes.names exes.buildable.libraries
111
+ ~pps ~dune_version
112
+ ~allow_overlaps: exes.buildable.allow_overlapping_dependencies
113
+ ~forbidden_libraries: exes.forbidden_libraries in
114
+ let + available = Lib.Compile. direct_requires compile_info in
115
+ Resolve. peek available in
116
+ match libs with
117
+ | Error () -> Memo.Build. return (acc, pps)
118
+ | Ok libs ->
119
+ Memo.Build.List. fold_left libs
120
+ ~init: (acc,pps)
121
+ ~f: (fun (acc , pps ) lib ->
122
+ let info = Lib. info lib in
123
+ (* Only select libraries that are not implementations.
124
+ Implementations are selected using the default implementation
125
+ feature. *)
126
+ let not_impl = Option. is_none (Lib_info. implements info) in
127
+ if not_impl
128
+ then
129
+ match Lib_info. kind info with
130
+ | Lib_kind. Ppx_rewriter _
131
+ | Ppx_deriver _ ->
132
+ Memo.Build. return
133
+ ( Appendable_list. ( @ ) (Appendable_list. singleton lib) acc
134
+ , Appendable_list. ( @ )
135
+ (Appendable_list. singleton
136
+ (Lib_info. loc info, Lib_info. name info))
137
+ pps )
138
+ | Normal ->
139
+ Memo.Build. return
140
+ ( Appendable_list. ( @ ) (Appendable_list. singleton lib) acc
141
+ , pps )
142
+ else
143
+ Memo.Build. return
144
+ (acc, pps)
145
+ )
146
+ )
96
147
| _ -> Memo.Build. return (acc, pps)))
97
148
>> | fun (libs , pps ) ->
98
149
(Appendable_list. to_list libs, Appendable_list. to_list pps)
0 commit comments