@@ -180,48 +180,51 @@ module Dune_project = struct
180
180
181
181
let subst t ~map ~version =
182
182
let s =
183
- let replace_text start_ofs stop_ofs repl =
184
- sprintf " %s%s%s"
185
- (String. sub t.contents ~pos: 0 ~len: start_ofs)
186
- repl
187
- (String. sub t.contents ~pos: stop_ofs
188
- ~len: (String. length t.contents - stop_ofs))
189
- in
190
- match t.version with
191
- | Some v ->
192
- (* There is a [version] field, overwrite its argument *)
193
- replace_text v.loc_of_arg.start.pos_cnum v.loc_of_arg.stop.pos_cnum
194
- (Dune_lang. to_string (Dune_lang. atom_or_quoted_string version))
195
- | None ->
196
- let version_field =
197
- Dune_lang. to_string
198
- (List
199
- [ Dune_lang. atom " version"
200
- ; Dune_lang. atom_or_quoted_string version
201
- ])
202
- ^ " \n "
203
- in
204
- let ofs =
205
- ref
206
- (match t.name with
207
- | Some { loc; _ } ->
208
- (* There is no [version] field but there is a [name] one, add the
209
- version after it *)
210
- loc.stop.pos_cnum
211
- | None ->
212
- (* If all else fails, add the [version] field after the first line
213
- of the file *)
214
- 0 )
183
+ match version with
184
+ | None -> t.contents
185
+ | Some version -> (
186
+ let replace_text start_ofs stop_ofs repl =
187
+ sprintf " %s%s%s"
188
+ (String. sub t.contents ~pos: 0 ~len: start_ofs)
189
+ repl
190
+ (String. sub t.contents ~pos: stop_ofs
191
+ ~len: (String. length t.contents - stop_ofs))
215
192
in
216
- let len = String. length t.contents in
217
- while ! ofs < len && t.contents.[! ofs] <> '\n' do
218
- incr ofs
219
- done ;
220
- if ! ofs < len && t.contents.[! ofs] = '\n' then (
221
- incr ofs;
222
- replace_text ! ofs ! ofs version_field
223
- ) else
224
- replace_text ! ofs ! ofs (" \n " ^ version_field)
193
+ match t.version with
194
+ | Some v ->
195
+ (* There is a [version] field, overwrite its argument *)
196
+ replace_text v.loc_of_arg.start.pos_cnum v.loc_of_arg.stop.pos_cnum
197
+ (Dune_lang. to_string (Dune_lang. atom_or_quoted_string version))
198
+ | None ->
199
+ let version_field =
200
+ Dune_lang. to_string
201
+ (List
202
+ [ Dune_lang. atom " version"
203
+ ; Dune_lang. atom_or_quoted_string version
204
+ ])
205
+ ^ " \n "
206
+ in
207
+ let ofs =
208
+ ref
209
+ (match t.name with
210
+ | Some { loc; _ } ->
211
+ (* There is no [version] field but there is a [name] one, add
212
+ the version after it *)
213
+ loc.stop.pos_cnum
214
+ | None ->
215
+ (* If all else fails, add the [version] field after the first
216
+ line of the file *)
217
+ 0 )
218
+ in
219
+ let len = String. length t.contents in
220
+ while ! ofs < len && t.contents.[! ofs] <> '\n' do
221
+ incr ofs
222
+ done ;
223
+ if ! ofs < len && t.contents.[! ofs] = '\n' then (
224
+ incr ofs;
225
+ replace_text ! ofs ! ofs version_field
226
+ ) else
227
+ replace_text ! ofs ! ofs (" \n " ^ version_field))
225
228
in
226
229
let s = Option. value (subst_string s ~map filename) ~default: s in
227
230
if s <> t.contents then Io. write_file filename s
230
233
let make_watermark_map ~commit ~version ~dune_project ~info =
231
234
let dune_project = Dune_project. project dune_project in
232
235
let version_num =
236
+ let open Option.O in
237
+ let + version = version in
233
238
Option. value ~default: version (String. drop_prefix version ~prefix: " v" )
234
239
in
235
240
let name = Dune_project. name dune_project in
@@ -250,11 +255,18 @@ let make_watermark_map ~commit ~version ~dune_project ~info =
250
255
| Some (Package.Source_kind. Url url ) -> Ok url
251
256
| None -> Error (sprintf " variable dev-repo not found in dune-project file" )
252
257
in
258
+ let make_version = function
259
+ | Some s -> Ok s
260
+ | None -> Error " repository does not contain any version information"
261
+ in
253
262
String.Map. of_list_exn
254
263
[ (" NAME" , Ok (Dune_project.Name. to_string_hum name))
255
- ; (" VERSION" , Ok version)
256
- ; (" VERSION_NUM" , Ok version_num)
257
- ; (" VCS_COMMIT_ID" , Ok commit)
264
+ ; (" VERSION" , make_version version)
265
+ ; (" VERSION_NUM" , make_version version_num)
266
+ ; ( " VCS_COMMIT_ID"
267
+ , match commit with
268
+ | None -> Error " repositroy does not contain any commits"
269
+ | Some s -> Ok s )
258
270
; ( " PKG_MAINTAINER"
259
271
, make_separated " maintainer" " , " @@ Package.Info. maintainers info )
260
272
; (" PKG_AUTHORS" , make_separated " authors" " , " @@ Package.Info. authors info)
0 commit comments