@@ -374,30 +374,22 @@ module T = struct
374374 ; pps : t list Resolve .t
375375 ; resolved_selects : Resolved_select .t list Resolve .t
376376 ; parameters : t list Resolve .t
377- ; arguments : argument option list
377+ ; arguments : t option list
378378 ; implements : t Resolve .t option
379379 ; project : Dune_project .t option
380380 ; (* these fields cannot be forced until the library is instantiated *)
381381 default_implementation : t Resolve .t Memo.Lazy .t option
382382 ; sub_systems : Sub_system0.Instance .t Memo.Lazy .t Sub_system_name.Map .t
383383 }
384384
385- and argument =
386- { arg : t
387- ; param_name : Module_name .t
388- ; arg_name : Module_name .t
389- ; loc : Loc .t
390- }
391-
392385 let rec compare (x : t ) (y : t ) =
393386 match Id. compare x.unique_id y.unique_id with
394387 | (Lt | Gt ) as cmp -> cmp
395388 | Eq -> compare_arguments x y
396389
397390 and compare_arguments a b =
398- List. compare a.arguments b.arguments ~compare: (Option. compare compare_argument)
399-
400- and compare_argument x y = compare x.arg y.arg
391+ List. compare a.arguments b.arguments ~compare: (Option. compare compare)
392+ ;;
401393
402394 let to_dyn t =
403395 Dyn. record
@@ -518,34 +510,27 @@ let resolve_main_module_name t =
518510let main_module_name t = Memo. return (resolve_main_module_name t)
519511
520512module Parameterised = struct
521- type nonrec argument = argument =
522- { arg : t
523- ; param_name : Module_name .t
524- ; arg_name : Module_name .t
525- ; loc : Loc .t
526- }
527-
528513 type status =
529514 | Not_parameterised
530515 | Partial
531516 | Complete
532517
533518 let status t =
534- if List. for_all t.arguments ~f: Option. is_none
535- then Not_parameterised
536- else (
519+ match t.arguments with
520+ | [] -> Not_parameterised
521+ | _ ->
537522 let rec check_instantiate lib =
538523 List. for_all lib.arguments ~f: (function
539524 | None -> false
540- | Some arg -> check_instantiate arg.arg )
525+ | Some arg -> check_instantiate arg)
541526 in
542- if check_instantiate t then Complete else Partial )
527+ if check_instantiate t then Complete else Partial
543528 ;;
544529
545530 let arguments t =
546531 List. map t.arguments ~f: (function
547532 | None -> Code_error. raise " expected complete application" [ " lib" , to_dyn t ]
548- | Some { arg; _ } -> arg)
533+ | Some arg -> arg)
549534 ;;
550535
551536 let parameterised_arguments t =
@@ -594,19 +579,12 @@ module Parameterised = struct
594579 let make_argument (loc , arg ) =
595580 let open Resolve.O in
596581 let * arg = arg in
597- let * param =
582+ let + param =
598583 match arg.implements with
599584 | Some param -> param
600585 | None -> Error. missing_implements ~loc arg.info
601586 in
602- let + param_name = resolve_main_module_name param
603- and + arg_name = resolve_main_module_name arg in
604- ( param
605- , { arg
606- ; param_name = Option. value_exn param_name
607- ; arg_name = Option. value_exn arg_name
608- ; loc
609- } )
587+ param, arg
610588 ;;
611589
612590 let make_arguments arguments =
@@ -644,9 +622,9 @@ module Parameterised = struct
644622 Resolve.List. map dep.arguments ~f: (fun opt_arg ->
645623 match opt_arg with
646624 | None -> Resolve. return None
647- | Some argument ->
648- let + arg = apply_arguments argument. arg parent_arguments in
649- Some { argument with arg } )
625+ | Some arg ->
626+ let + arg = apply_arguments arg parent_arguments in
627+ Some arg)
650628 in
651629 apply_arguments { dep with arguments } parent_arguments
652630 ;;
@@ -662,11 +640,11 @@ module Parameterised = struct
662640 let lib_arguments =
663641 List. filter_map lib.arguments ~f: (function
664642 | None -> None
665- | Some arg -> Some arg.arg )
643+ | Some arg -> Some arg)
666644 in
667645 let deps = lib_arguments @ deps in
668646 let deps =
669- match lib_arguments with
647+ match lib.arguments with
670648 | [] -> deps
671649 | _ -> remove_arguments lib :: deps
672650 in
@@ -699,12 +677,12 @@ module Parameterised = struct
699677
700678 let rec for_instance ~build_dir ~ext_lib t =
701679 match info ~build_dir ~ext_lib t with
702- | None -> { t with arguments = [] }
680+ | None -> remove_arguments t
703681 | Some info ->
704682 let arguments =
705683 List. map t.arguments ~f: (function
706684 | None -> None
707- | Some arg -> Some { arg with arg = for_instance ~build_dir ~ext_lib arg.arg } )
685+ | Some arg -> Some ( for_instance ~build_dir ~ext_lib arg) )
708686 in
709687 { t with info = Lib_info. of_local info; arguments }
710688 ;;
@@ -2567,7 +2545,7 @@ let to_dune_lib
25672545 ; arguments =
25682546 List. filter_map args ~f: (function
25692547 | None -> None
2570- | Some arg -> Some (arg.loc , mangled_name arg. arg))
2548+ | Some arg -> Some (Loc. none , mangled_name arg))
25712549 ; new_name = None
25722550 }))
25732551 in
0 commit comments