File tree Expand file tree Collapse file tree 4 files changed +14
-14
lines changed Expand file tree Collapse file tree 4 files changed +14
-14
lines changed Original file line number Diff line number Diff line change @@ -1482,8 +1482,8 @@ and precompile_or ~arg_id (cls : Simple.clause list) ors args def k =
14821482              (*  bound variables of the or-pattern and used in the orpm
14831483                 actions *)  
14841484              Typedtree. pat_bound_idents_full orp
1485-               |>  List. filter (fun  (id , _ ) -> Ident.Set. mem id pm_fv)
1486-               |>  List. map (fun  (id , ty ) ->
1485+               |>  List. filter (fun  (id , _ ,  _ ) -> Ident.Set. mem id pm_fv)
1486+               |>  List. map (fun  (id , _ ,  ty ) ->
14871487                     (id, Typeopt. value_kind orp.pat_env ty))
14881488            in 
14891489            let  or_num =  next_raise_count ()  in 
@@ -3595,10 +3595,10 @@ let for_let ~scopes loc param pat body =
35953595      let  catch_ids =  pat_bound_idents_full pat in 
35963596      let  ids_with_kinds = 
35973597        List. map
3598-           (fun  (id , typ ) -> (id, Typeopt. value_kind pat.pat_env typ))
3598+           (fun  (id , _ ,  typ ) -> (id, Typeopt. value_kind pat.pat_env typ))
35993599          catch_ids
36003600      in 
3601-       let  ids =  List. map (fun  (id , _ ) -> id) catch_ids in 
3601+       let  ids =  List. map (fun  (id , _ ,  _ ) -> id) catch_ids in 
36023602      let  bind = 
36033603        map_return (assign_pat ~scopes  opt nraise ids loc pat) param in 
36043604      if  ! opt then 
Original file line number Diff line number Diff line change @@ -1336,9 +1336,9 @@ and transl_match ~scopes e arg pat_expr_list partial =
13361336        (*  Simplif doesn't like it if binders are not uniq, so we make sure to
13371337           use different names in the value and the exception branches. *)  
13381338        let  ids_full =  Typedtree. pat_bound_idents_full pv in 
1339-         let  ids =  List. map (fun  (id , _ ) -> id) ids_full in 
1339+         let  ids =  List. map (fun  (id , _ ,  _ ) -> id) ids_full in 
13401340        let  ids_kinds = 
1341-           List. map (fun  (id , ty ) -> id, Typeopt. value_kind pv.pat_env ty)
1341+           List. map (fun  (id , _ ,  ty ) -> id, Typeopt. value_kind pv.pat_env ty)
13421342            ids_full
13431343        in 
13441344        let  vids =  List. map Ident. rename ids in 
Original file line number Diff line number Diff line change @@ -779,11 +779,11 @@ let rec iter_bound_idents
779779  : type  k  . _  -> k  general_pattern  -> _  
780780  =  fun  f  pat  -> 
781781  match  pat.pat_desc with  
782-   |  Tpat_var  (id , _ ) -> 
783-      f (id,  pat.pat_type) 
784-   |  Tpat_alias (p , id , _ ) -> 
782+   |  Tpat_var  (id , s ) -> 
783+      f (id,s, pat.pat_type) 
784+   |  Tpat_alias (p , id , s ) -> 
785785      iter_bound_idents f p; 
786-       f (id,  pat.pat_type) 
786+       f (id,s, pat.pat_type) 
787787  |  Tpat_or (p1 , _ , _ ) -> 
788788      (*  Invariant : both arguments bind the same variables *)  
789789      iter_bound_idents f p1 
@@ -799,7 +799,7 @@ let rev_pat_bound_idents_full pat =
799799  ! idents_full 
800800
801801let  rev_only_idents  idents_full  = 
802-   List. rev_map (fun  (id ,_ ) -> id) idents_full 
802+   List. rev_map (fun  (id ,_ , _ ) -> id) idents_full 
803803
804804let  pat_bound_idents_full  pat  = 
805805  List. rev (rev_pat_bound_idents_full pat) 
@@ -826,7 +826,7 @@ let let_bound_idents_with_modes bindings =
826826  in  
827827  List. iter (fun  vb  -> loop vb.vb_pat) bindings; 
828828  List. rev_map 
829-     (fun  (id , _ ) -> id, List. rev (Ident.Tbl. find_all modes id)) 
829+     (fun  (id , _ ,  _ ) -> id, List. rev (Ident.Tbl. find_all modes id)) 
830830    (rev_let_bound_idents_full bindings) 
831831
832832let  let_bound_idents_full  bindings  = 
Original file line number Diff line number Diff line change @@ -821,7 +821,7 @@ val exists_pattern: (pattern -> bool) -> pattern -> bool
821821
822822val  let_bound_idents : value_binding  list  -> Ident .t  list 
823823val  let_bound_idents_full :
824-     value_binding  list  -> (Ident .t  *  Types .type_expr ) list 
824+     value_binding  list  -> (Ident .t  *  string   loc   *   Types .type_expr ) list 
825825val  let_bound_idents_with_modes :
826826  value_binding  list 
827827  -> (Ident .t  *  (Location .t  *  Types .value_mode ) list ) list 
@@ -835,7 +835,7 @@ val mkloc: 'a -> Location.t -> 'a Asttypes.loc
835835
836836val  pat_bound_idents : 'k  general_pattern  -> Ident .t  list 
837837val  pat_bound_idents_full :
838-   'k  general_pattern  -> (Ident .t  *  Types .type_expr ) list 
838+   'k  general_pattern  -> (Ident .t  *  string   loc   *   Types .type_expr ) list 
839839
840840(* * Splits an or pattern into its value (left) and exception (right) parts. *) 
841841val  split_pattern :
 
 
   
 
     
   
   
          
    
    
     
    
      
     
     
    You can’t perform that action at this time.
  
 
    
  
    
      
        
     
       
      
     
   
 
    
    
  
 
  
 
     
    
0 commit comments