Coccinelle release-1.0.0-rc11
[bpt/coccinelle.git] / parsing_c / unparse_c.ml
index 0cabad4..c331b34 100644 (file)
@@ -1,6 +1,7 @@
 (* Yoann Padioleau, Julia Lawall
  *
- * Copyright (C) 2010, University of Copenhagen DIKU and INRIA.
+ * Copyright (C) 2012, INRIA.
+ * Copyright (C) 2010, 2011, University of Copenhagen DIKU and INRIA.
  * Copyright (C) 2006, 2007, 2008, 2009 Ecole des Mines de Nantes and DIKU
  *
  * This program is free software; you can redistribute it and/or
@@ -51,17 +52,21 @@ type token1 =
  * type.
  *)
 type min =
-    Min of (int list (* match numbers *) * int (* adjacency information *))
+    Min of (int list (* match numbers from witness trees *) *
+             Ast_cocci.adjacency (* adjacency information *))
   | Ctx
 
 type token2 =
   | T2 of Parser_c.token * min *
           int option (* orig index, abstracting away comments and space *)
-  | Fake2
+  | Fake2 of min
   | Cocci2 of string * int (* line *) * int (* lcol *) * int (* rcol *)
+       * Unparse_cocci.nlhint option
   | C2 of string
+  | Comma of string
   | Indent_cocci2
   | Unindent_cocci2 of bool (* true for permanent, false for temporary *)
+  | EatSpace2
 
 (* not used yet *)
 type token3 =
@@ -95,29 +100,50 @@ let print_token1 = function
 
 let str_of_token2 = function
   | T2 (t,_,_) -> TH.str_of_tok t
-  | Fake2 -> ""
-  | Cocci2 (s,_,_,_) -> s
+  | Fake2 -> ""
+  | Cocci2 (s,_,_,_,_) -> s
   | C2 s -> s
+  | Comma s -> s
   | Indent_cocci2 -> ""
   | Unindent_cocci2 _ -> ""
+  | EatSpace2 -> ""
 
 let print_token2 = function
   | T2 (t,b,_) ->
+      let t_str =
+       match t with
+       | Parser_c.TCommentSpace _ -> " sp "
+       | Parser_c.TCommentNewline _ -> " nl "
+       | Parser_c.TCommentCpp _ -> " cp "
+       | Parser_c.TCommentMisc _ -> " misc "
+       | Parser_c.TComment _ -> " comment "
+       | _ -> "" in
       let b_str =
        match b with
          Min (index,adj) ->
-           Printf.sprintf "-%d[%s]" adj
+           Printf.sprintf "-%d[%s]"
+             (match adj with Ast_cocci.ADJ n -> n | _ -> -1)
              (String.concat " " (List.map string_of_int index))
        | Ctx -> "" in
-      "T2:"^b_str^TH.str_of_tok t
-  | Fake2 -> "fake"
-  | Cocci2 (s,_,lc,rc) -> Printf.sprintf "Cocci2:%d:%d%s" lc rc s
+      "T2:"^b_str^t_str^TH.str_of_tok t
+  | Fake2 b ->
+      let b_str =
+       match b with
+         Min (index,adj) ->
+           Printf.sprintf "-%d[%s]"
+             (match adj with Ast_cocci.ADJ n -> n | _ -> -1)
+             (String.concat " " (List.map string_of_int index))
+       | Ctx -> "" in
+      b_str^"fake"
+  | Cocci2 (s,_,lc,rc,_) -> Printf.sprintf "Cocci2:%d:%d%s" lc rc s
   | C2 s -> "C2:"^s
+  | Comma s -> "Comma:"^s
   | Indent_cocci2 -> "Indent"
   | Unindent_cocci2 _ -> "Unindent"
+  | EatSpace2 -> "EatSpace"
 
 let simple_print_all_tokens1 l =
-  List.iter (function x -> Printf.printf "%s " (print_token1 x)) l;
+  List.iter (function x -> Printf.printf "|%s| " (print_token1 x)) l;
   Printf.printf "\n"
 
 let simple_print_all_tokens2 l =
@@ -157,8 +183,8 @@ let mcode_contain_plus = function
   | Ast_cocci.CONTEXT (_,Ast_cocci.NOTHING) -> false
   | Ast_cocci.CONTEXT _ -> true
 (* patch: when need full coccinelle transformation *)
-  | Ast_cocci.MINUS (_,_,_,[]) -> false
-  | Ast_cocci.MINUS (_,_,_,x::xs) -> true
+  | Ast_cocci.MINUS (_,_,_,Ast_cocci.NOREPLACEMENT) -> false
+  | Ast_cocci.MINUS (_,_,_,Ast_cocci.REPLACEMENT _) -> true(*REPL is not empty*)
   | Ast_cocci.PLUS _ -> raise Impossible
 
 let contain_plus info =
@@ -221,7 +247,7 @@ let get_fakeInfo_and_tokens celem toks =
         (* get the associated comments/space/cppcomment tokens *)
         let (before, x, after) =
          !toks_in +> Common.split_when (fun tok ->
-         info =*= TH.info_of_tok tok)
+           info =*= TH.info_of_tok tok)
         in
         assert(info =*= TH.info_of_tok x);
         (*old: assert(before +> List.for_all (TH.is_comment)); *)
@@ -249,7 +275,7 @@ let get_fakeInfo_and_tokens celem toks =
 
   List.rev !toks_out
 
-(* Fake nodes that have BEFORE code should be moved over any subsequent
+(* Fake nodes that have BEFORE code or are - should be moved over any subsequent
 whitespace and newlines, but not any comments, to get as close to the affected
 code as possible.  Similarly, fake nodes that have AFTER code should be moved
 backwards.  No fake nodes should have both before and after code. *)
@@ -270,7 +296,8 @@ let displace_fake_nodes toks =
        (match !(info.cocci_tag) with
         | Some x ->
           (match x with
-           (Ast_cocci.CONTEXT(_,Ast_cocci.BEFORE _),_) ->
+           (Ast_cocci.CONTEXT(_,Ast_cocci.BEFORE _),_)
+         | (Ast_cocci.MINUS(_,_,_,Ast_cocci.REPLACEMENT _),_) ->
            (* move the fake node forwards *)
              let (whitespace,rest) = Common.span is_whitespace aft in
              bef @ whitespace @ fake :: (loop rest)
@@ -299,7 +326,12 @@ let displace_fake_nodes toks =
 (*****************************************************************************)
 
 let comment2t2 = function
-    (Token_c.TCommentCpp x,(info : Token_c.info)) ->
+    (Token_c.TCommentCpp
+       (* not sure iif the following list is exhaustive or complete *)
+       (Token_c.CppAttr|Token_c.CppMacro|Token_c.CppPassingCosWouldGetError),
+     (info : Token_c.info)) ->
+      C2(info.Common.str)
+  | (Token_c.TCommentCpp x,(info : Token_c.info)) ->
       C2("\n"^info.Common.str^"\n")
   | x -> failwith (Printf.sprintf "unexpected comment %s" (Common.dump x))
 
@@ -313,9 +345,10 @@ let expand_mcode toks =
     | Fake1 info ->
         let str = Ast_c.str_of_info info in
         if str =$= ""
-        then push2 (Fake2) toks_out
-        (* perhaps the fake ',' *)
-        else push2 (C2 str) toks_out
+        then push2 (Fake2 minus) toks_out
+       (* fx the fake "," at the end of a structure or enum.
+          no idea what other fake info there can be... *)
+       else push2 (Comma str) toks_out
 
 
     | T1 tok ->
@@ -354,8 +387,8 @@ let expand_mcode toks =
     let (mcode,env) =
       Ast_c.mcode_and_env_of_cocciref ((info_of_token1 t).cocci_tag) in
 
-    let pr_cocci s ln col rcol =
-      push2 (Cocci2(s,ln,col,rcol)) toks_out  in
+    let pr_cocci s ln col rcol hint =
+      push2 (Cocci2(s,ln,col,rcol,hint)) toks_out  in
     let pr_c info =
       (match Ast_c.pinfo_of_info info with
        Ast_c.AbstractLineTok _ ->
@@ -369,7 +402,7 @@ let expand_mcode toks =
       List.iter (fun x -> Common.push2 (comment2t2 x) toks_out) in
 
     let pr_barrier ln col = (* marks a position, used around C code *)
-      push2 (Cocci2("",ln,col,col)) toks_out  in
+      push2 (Cocci2("",ln,col,col,None)) toks_out  in
     let pr_nobarrier ln col = () in (* not needed for linux spacing *)
 
     let pr_cspace _ = push2 (C2 " ") toks_out in
@@ -379,6 +412,7 @@ let expand_mcode toks =
 
     let indent _   = push2 Indent_cocci2 toks_out in
     let unindent x = push2 (Unindent_cocci2 x) toks_out in
+    let eat_space _   = push2 EatSpace2 toks_out in
 
     let args_pp =
       (env, pr_cocci, pr_c, pr_cspace,
@@ -387,7 +421,7 @@ let expand_mcode toks =
        pr_arity,
        (match !Flag_parsing_c.spacing with
         Flag_parsing_c.SMPL -> pr_barrier | _ -> pr_nobarrier),
-       indent, unindent) in
+       indent, unindent, eat_space) in
 
     (* old: when for yacfe with partial cocci:
      *    add_elem t false;
@@ -401,7 +435,10 @@ let expand_mcode toks =
          * set of tokens, so I can then process and remove the
          * is_between_two_minus for instance *)
         add_elem t (Min (inst,adj));
-        unparser any_xxs Unparse_cocci.InPlace
+       (match any_xxs with
+         Ast_cocci.NOREPLACEMENT -> ()
+       | Ast_cocci.REPLACEMENT(any_xxs,_) ->
+            unparser any_xxs Unparse_cocci.InPlace)
     | Ast_cocci.CONTEXT (_,any_befaft) ->
         (match any_befaft with
         | Ast_cocci.NOTHING ->
@@ -489,7 +526,8 @@ let is_minusable_comment_nocpp = function
   | _ -> false
 
 let all_coccis = function
-    Cocci2 _ | C2 _ | Indent_cocci2 | Unindent_cocci2 _ -> true
+    Cocci2 _ | C2 _ | Comma _ | Indent_cocci2 | Unindent_cocci2 _
+  | EatSpace2 -> true
   | _ -> false
 
 (*previously gave up if the first character was a newline, but not clear why*)
@@ -515,10 +553,12 @@ let set_minus_comment adj = function
       T2 (t, Min adj, idx)
 (* patch: coccinelle *)
   | T2 (t,Min adj,idx) as x -> x
+  | Fake2 _ as x -> x
   | _ -> raise Impossible
 
 let set_minus_comment_or_plus adj = function
-    Cocci2 _ | C2 _ | Indent_cocci2 | Unindent_cocci2 _ as x -> x
+    Cocci2 _ | C2 _ | Comma _ | Indent_cocci2 | Unindent_cocci2 _
+  | EatSpace2 as x -> x
   | x -> set_minus_comment adj x
 
 let drop_minus xs =
@@ -527,16 +567,22 @@ let drop_minus xs =
     | _ -> false
   )
 
-let remove_minus_and_between_and_expanded_and_fake xs =
-
-  (* get rid of exampled and fake tok *)
-  let xs = xs +> Common.exclude (function
+let drop_expanded xs =
+  xs +> Common.exclude (function
     | T2 (t,_,_) when TH.is_expanded t -> true
-    | Fake2 -> true
+    | _ -> false
+  )
 
+let drop_fake xs =
+  xs +> Common.exclude (function
+    | Fake2 _ -> true
     | _ -> false
   )
-  in
+
+let remove_minus_and_between_and_expanded_and_fake xs =
+
+  (* get rid of expanded tok *)
+  let xs = drop_expanded xs in
 
   let minus_or_comment = function
       T2(_,Min adj,_) -> true
@@ -547,59 +593,14 @@ let remove_minus_and_between_and_expanded_and_fake xs =
     | x -> is_minusable_comment_nocpp x in
 
   let common_adj (index1,adj1) (index2,adj2) =
-    adj1 = adj2 (* same adjacency info *) &&
+    let same_adj = (* same adjacency info *)
+      match (adj1,adj2) with
+       (Ast_cocci.ADJ adj1,Ast_cocci.ADJ adj2) -> adj1 = adj2
+      | (Ast_cocci.ALLMINUS,_) | (_,Ast_cocci.ALLMINUS) -> true in
+    same_adj &&
     (* non-empty intersection of witness trees *)
     not ((Common.inter_set index1 index2) = []) in
 
-  let rec adjust_around_minus = function
-      [] -> []
-    | (T2(Parser_c.TCommentNewline c,_b,_i) as x)::
-      (((T2(_,Min adj,_))::_) as rest) ->
-       (* an initial newline, as in a replaced statement *)
-       let (between_minus,rest) = Common.span minus_or_comment rest in
-       (match rest with
-         [] -> (set_minus_comment adj x) ::
-           (List.map (set_minus_comment adj) between_minus)
-       | T2(_,Ctx,_)::_ when is_newline (List.hd(List.rev between_minus)) ->
-           (set_minus_comment adj x)::(adjust_within_minus between_minus) @
-           (adjust_around_minus rest)
-       | _ ->
-           x :: (adjust_within_minus between_minus) @
-           (adjust_around_minus rest))
-    | ((T2(_,Min adj,_))::_) as rest ->
-       (* no initial newline, as in a replaced expression *)
-       let (between_minus,rest) = Common.span minus_or_comment rest in
-       (match rest with
-         [] ->
-           (List.map (set_minus_comment adj) between_minus)
-       | _ ->
-           (adjust_within_minus between_minus) @
-           (adjust_around_minus rest))
-    | x::xs -> x::adjust_around_minus xs
-  and adjust_within_minus = function
-      [] -> []
-    | (T2(_,Min adj1,_) as t1)::xs ->
-       let (between_minus,rest) = Common.span is_minusable_comment xs in
-       (match rest with
-          [] ->
-           (* keep last newline *)
-           let (drop,keep) =
-             try
-               let (drop,nl,keep) =
-                 Common.split_when is_newline between_minus in
-               (drop, nl :: keep)
-             with Not_found -> (between_minus,[]) in
-           t1 ::
-           List.map (set_minus_comment_or_plus adj1) drop @
-           keep
-       | (T2(_,Min adj2,_) as t2)::rest when common_adj adj1 adj2 ->
-           t1::
-            List.map (set_minus_comment_or_plus adj1) between_minus @
-            adjust_within_minus (t2::rest)
-       | x::xs ->
-           t1::(between_minus @ adjust_within_minus (x::xs)))
-    | _ -> failwith "only minus and space possible" in
-
   (* new idea: collects regions not containing non-space context code
      if two adjacent adjacent minus tokens satisfy common_adj then delete
      all spaces, comments etc between them
@@ -611,7 +612,7 @@ let remove_minus_and_between_and_expanded_and_fake xs =
   let rec adjust_around_minus = function
       [] -> []
     | (T2(Parser_c.TCommentNewline c,_b,_i) as x)::
-      (T2(_,Min adj1,_) as t1)::xs ->
+      ((Fake2(Min adj1) | T2(_,Min adj1,_)) as t1)::xs ->
        let (minus_list,rest) = Common.span not_context (t1::xs) in
        let contains_plus = List.exists is_plus minus_list in
        let x =
@@ -622,33 +623,35 @@ let remove_minus_and_between_and_expanded_and_fake xs =
          | _ -> x in
        x :: adjust_within_minus contains_plus minus_list @
        adjust_around_minus rest
-    | (T2(_,Min adj1,_) as t1)::xs ->
+    | ((Fake2(Min adj1) | T2(_,Min adj1,_)) as t1)::xs ->
        let (minus_list,rest) = Common.span not_context (t1::xs) in
        let contains_plus = List.exists is_plus minus_list in
        adjust_within_minus contains_plus minus_list @ adjust_around_minus rest
-    | x::xs -> x :: adjust_around_minus xs
+    | x::xs ->
+       x :: adjust_around_minus xs
   and adjust_within_minus cp (* contains plus *) = function
-      (T2(_,Min adj1,_) as t1)::xs ->
+      ((Fake2(Min adj1) | T2(_,Min adj1,_)) as t1)::xs ->
        let not_minus = function T2(_,Min _,_) -> false | _ -> true in
        let (not_minus_list,rest) = Common.span not_minus xs in
        t1 ::
        (match rest with
-         (T2(_,Min adj2,_) as t2)::xs when common_adj adj1 adj2 ->
+         ((Fake2(Min adj2) | T2(_,Min adj2,_)) as t2)::xs
+         when common_adj adj1 adj2 ->
            (List.map (set_minus_comment_or_plus adj1) not_minus_list)
            @ (adjust_within_minus cp (t2::xs))
-       | (T2(_,Min adj2,_) as t2)::xs ->
-           let is_whitespace_or_plus = function
-               (T2 _) as x -> is_space x
-             | _ -> true (*plus*) in
-           if List.for_all is_whitespace_or_plus not_minus_list
+       | ((Fake2(Min adj2) | T2(_,Min adj2,_)) as t2)::xs ->
+           if not cp && List.for_all is_whitespace not_minus_list
            then
              (List.map (set_minus_comment_or_plus adj1) not_minus_list)
              @ (adjust_within_minus cp (t2::xs))
-           else not_minus_list @ (adjust_within_minus cp (t2::xs))
+           else
+             not_minus_list @ (adjust_within_minus cp (t2::xs))
        | _ ->
            if cp
            then xs
            else
+             (* remove spaces after removed stuff, eg a comma after a
+                function argument *)
              let (spaces,rest) = Common.span is_space xs in
              (List.map (set_minus_comment_or_plus adj1) spaces)
              @ rest)
@@ -657,11 +660,14 @@ let remove_minus_and_between_and_expanded_and_fake xs =
       (T2(_,Ctx,_) as x) when not (is_minusable_comment x) -> false
     | _ -> true
   and is_plus = function
-      C2 _ | Cocci2 _ -> true
+      C2 _ | Comma _ | Cocci2 _ -> true
     | _ -> false in
 
   let xs = adjust_around_minus xs in
 
+  (* get rid of fake tok *)
+  let xs = drop_fake xs in
+
   (* this drops blank lines after a brace introduced by removing code *)
   let minus_or_comment_nonl = function
       T2(_,Min adj,_) -> true
@@ -722,12 +728,34 @@ let remove_minus_and_between_and_expanded_and_fake xs =
        m ::
        (List.map (set_minus_comment adj) spaces) @
        (adjust_before_brace rest)
+    | ((T2 (t0, Ctx, idx0)) as m0) :: ((T2 (t, Min adj, idx)) as m) :: rest
+       when TH.str_of_tok t0 = "" ->
+         (* This is for the case of a #define that is completely deleted,
+            because a #define has a strange EOL token at the end.
+            We hope there i no other kind of token that is represented by
+            "", but it seems like changing the kind of token might break
+            the end of entity recognition in the C parser.
+            See parsing_hacks.ml *)
+         let (spaces,rest) = Common.span minus_or_comment_nocpp rest in
+         m0 :: m ::
+         (List.map (set_minus_comment adj) spaces) @
+         (adjust_before_brace rest)
     | rest -> adjust_before_brace rest in
 
   let xs = List.rev (from_newline (List.rev xs)) in
   let xs = drop_minus xs in
   xs
 
+(* things that should not be followed by space - boundary between SmPL
+   code and C code *)
+let adjust_eat_space toks =
+  let rec loop = function
+      [] -> []
+    | EatSpace2 :: x :: rest when is_space x -> loop rest
+    | EatSpace2 :: rest -> loop rest
+    | x :: xs -> x :: loop xs in
+  loop toks
+
 (* normally, in C code, a semicolon is not preceded by a space or newline *)
 let adjust_before_semicolon toks =
   let toks = List.rev toks in
@@ -735,7 +763,7 @@ let adjust_before_semicolon toks =
       [] -> []
     | ((T2(_,Ctx,_)) as x)::xs | ((Cocci2 _) as x)::xs ->
        if List.mem (str_of_token2 x) [";";")";","]
-       then x :: search_minus false xs
+       then x :: search_semic (search_minus false xs)
        else x :: search_semic xs
     | x::xs -> x :: search_semic xs
   and search_minus seen_minus xs =
@@ -746,27 +774,206 @@ let adjust_before_semicolon toks =
     | _ -> if seen_minus then rest else xs in
   List.rev (search_semic toks)
 
+(* normally, in C code, a ( is not followed by a space or newline *)
+let adjust_after_paren toks =
+  let rec search_paren = function
+      [] -> []
+    | ((T2(_,Ctx,_)) as x)::xs | ((Cocci2 _) as x)::xs ->
+       if List.mem (str_of_token2 x) ["("] (* other things? *)
+       then x :: search_paren(search_minus false xs)
+       else x :: search_paren xs
+    | x::xs -> x :: search_paren xs
+  and search_minus seen_minus xs =
+    let (spaces, rest) = Common.span is_whitespace xs in
+    (* only delete spaces if something is actually deleted *)
+    match rest with
+      ((T2(_,Min _,_)) as a)::rerest -> (* minus *)
+       a :: search_minus true rerest
+    | ((T2(_,Ctx,_)) as a)::rerest when seen_minus && str_of_token2 a = "," ->
+       (* comma after ( will be deleted, so consider it as minus code
+          already *)
+       a :: search_minus true rerest
+    | _ -> if seen_minus then rest else xs in (* drop trailing space *)
+  search_paren toks
+
+(* this is for the case where braces are added around an if branch *)
+let paren_then_brace toks =
+  let rec search_paren = function
+      [] -> []
+    | ((T2(_,Ctx,_)) as x)::xs ->
+       if List.mem (str_of_token2 x) [")"]
+       then x :: search_paren(search_plus xs)
+       else x :: search_paren xs
+    | x::xs -> x :: search_paren xs
+  and search_plus xs =
+    let (spaces, rest) = Common.span is_whitespace xs in
+    match rest with
+      (* move the brace up to the previous line *)
+      ((Cocci2("{",_,_,_,_)) as x) :: (((Cocci2 _) :: _) as rest) ->
+       (C2 " ") :: x :: spaces @ rest
+    | _ -> xs in
+  search_paren toks
+
 let is_ident_like s = s ==~ Common.regexp_alpha
 
+let rec drop_space_at_endline = function
+    [] -> []
+  | [x] -> [x]
+  | (C2 " ") ::
+    ((((T2(Parser_c.TCommentSpace _,Ctx,_)) | Cocci2("\n",_,_,_,_) |
+    (T2(Parser_c.TCommentNewline _,Ctx,_))) :: _) as rest) ->
+      (* when unparse_cocci doesn't know whether space is needed *)
+      drop_space_at_endline rest
+  | ((T2(Parser_c.TCommentSpace _,Ctx,_i)) as a)::rest ->
+      let (outer_spaces,rest) = Common.span is_space rest in
+      let minus_or_comment_or_space_nocpp = function
+         T2(_,Min adj,_) -> true
+       | (T2(Parser_c.TCommentSpace _,Ctx,_i)) -> true
+       | (T2(Parser_c.TCommentNewline _,Ctx,_i)) -> false
+       | x -> false in
+      let (minus,rest) = Common.span minus_or_comment_or_space_nocpp rest in
+      let fail _ = a :: outer_spaces @ minus @ (drop_space_at_endline rest) in
+      if List.exists (function T2(_,Min adj,_) -> true | _ -> false) minus
+      then
+       match rest with
+         ((T2(Parser_c.TCommentNewline _,Ctx,_i)) as a)::rest ->
+           (* drop trailing spaces *)
+           minus@a::(drop_space_at_endline rest)
+       | _ -> fail()
+      else fail()
+  | a :: rest ->
+      a :: drop_space_at_endline rest
+
+(* if a removed ( is between two tokens, then add a space *)
+let rec paren_to_space = function
+    [] -> []
+  | [x] -> [x]
+  | [x;y] -> [x;y]
+  | ((T2(_,Ctx,_)) as a)::((T2(t,Min _,_)) as b)::((T2(_,Ctx,_)) as c)::rest
+    when not (is_whitespace a) && TH.str_of_tok t = "(" ->
+      a :: b :: (C2 " ") :: (paren_to_space (c :: rest))
+  | a :: rest -> a :: (paren_to_space rest)
+
 let rec add_space xs =
   match xs with
   | [] -> []
   | [x] -> [x]
-  | (Cocci2(sx,lnx,_,rcolx) as x)::((Cocci2(sy,lny,lcoly,_)) as y)::xs
+  | (Cocci2(sx,lnx,_,rcolx,_) as x)::((Cocci2(sy,lny,lcoly,_,_)) as y)::xs
     when !Flag_parsing_c.spacing = Flag_parsing_c.SMPL &&
       not (lnx = -1) && lnx = lny && not (rcolx = -1) && rcolx < lcoly ->
        (* this only works within a line.  could consider whether
           something should be done to add newlines too, rather than
           printing them explicitly in unparse_cocci. *)
        x::C2 (String.make (lcoly-rcolx) ' ')::add_space (y::xs)
-  | x::y::xs ->
+  | (Cocci2(sx,lnx,_,rcolx,_) as x)::((Cocci2(sy,lny,lcoly,_,_)) as y)::xs
+    when !Flag_parsing_c.spacing = Flag_parsing_c.SMPL &&
+      not (lnx = -1) && lnx < lny && not (rcolx = -1) ->
+       (* this only works within a line.  could consider whether
+          something should be done to add newlines too, rather than
+          printing them explicitly in unparse_cocci. *)
+       x::C2 (String.make (lny-lnx) '\n')::
+       C2 (String.make (lcoly-1) ' '):: (* -1 is for the + *)
+       add_space (y::xs)
+  | ((T2(_,Ctx,_)) as x)::((Cocci2 _) as y)::xs -> (* add space on boundary *)
+      let sx = str_of_token2 x in
+      let sy = str_of_token2 y in
+      if is_ident_like sx && (is_ident_like sy or List.mem sy ["="])
+      then x::C2 " "::(add_space (y::xs))
+      else x::(add_space (y::xs))
+  | x::y::xs -> (* not boundary, not sure if it is possible *)
       let sx = str_of_token2 x in
       let sy = str_of_token2 y in
       if is_ident_like sx && is_ident_like sy
       then x::C2 " "::(add_space (y::xs))
       else x::(add_space (y::xs))
 
+(* A fake comma is added at the end of an unordered initlist or a enum
+decl, if the initlist or enum doesn't already end in a comma.  This is only
+needed if there is + code, ie if we see Cocci after it in the code sequence *)
 
+let rec drop_end_comma = function
+    [] -> []
+  | [x] -> [x]
+  | ((Comma ",") as x) :: rest ->
+      let (newlines,rest2) = Common.span is_whitespace rest in
+      (match rest2 with
+       (Cocci2 _) :: _ -> x :: drop_end_comma rest
+      |        _ -> drop_end_comma rest)
+  | x :: xs -> x :: drop_end_comma xs
+
+(* The following only works for the outermost function call.  Stack records
+the column of all open parentheses.  Space_cell contains the most recent
+comma in the outermost function call.  The goal is to decide whether this
+should be followed by a space or a newline and indent. *)
+let add_newlines toks tabbing_unit =
+  let create_indent n =
+    let (tu,tlen) = 
+      match tabbing_unit with
+       Some ("\t",_) -> ("\t",8)
+      | Some ("",_) -> ("\t",8) (* not sure why... *)
+      | Some (s,_) -> (s,String.length s) (* assuming only spaces *)
+      |        None -> ("\t",8) in
+    let rec loop seen =
+      if seen + tlen <= n
+      then tu ^ loop (seen + tlen)
+      else String.make (n-seen) ' ' in
+    loop 0 in
+  let check_for_newline count x = function
+      Some (start,space_cell) when count > Flag_parsing_c.max_width ->
+       space_cell := "\n"^(create_indent x);
+       Some (x + (count - start))
+    | _ -> None in
+  (* the following is for strings that may contain newline *)
+  let string_length s count =
+    let l = list_of_string s in
+    List.fold_left
+      (function count ->
+       function
+           '\t' -> count + 8
+         | '\n' -> 0
+         | c -> count + 1)
+      count l in
+  let rec loop info count = function
+      [] -> []
+    | ((T2(tok,_,_)) as a)::xs ->
+       a :: loop info (string_length (TH.str_of_tok tok) count) xs
+    | ((Cocci2(s,line,lcol,rcol,hint)) as a)::xs ->
+       let (stack,space_cell) = info in
+       let rest =
+         match hint with
+           None -> loop info (string_length s count) xs
+         | Some Unparse_cocci.StartBox ->
+             let count = string_length s count in
+             loop (count::stack,space_cell) count xs
+         | Some Unparse_cocci.EndBox ->
+             let count = string_length s count in
+             (match stack with
+               [x] ->
+                 (match check_for_newline count x space_cell with
+                   Some count -> loop ([],None) count xs
+                 | None -> loop ([],None) count xs)
+             | _ -> loop (List.tl stack,space_cell) count xs)
+         | Some (Unparse_cocci.SpaceOrNewline sp) ->
+             let count = string_length s (count + 1 (*space*)) in
+             (match stack with
+               [x] ->
+                 (match check_for_newline count x space_cell with
+                   Some count -> loop (stack,Some (x,sp)) count xs
+                 | None -> loop (stack,Some (count,sp)) count xs)
+             | _ -> loop info count xs) in
+       a :: rest
+    | ((C2(s)) as a)::xs -> a :: loop info (string_length s count) xs
+    | ((Comma(s)) as a)::xs -> a :: loop info (string_length s count) xs
+    | Fake2 _ :: _ | Indent_cocci2 :: _
+    | Unindent_cocci2 _::_ | EatSpace2::_ ->
+       failwith "unexpected fake, indent, unindent, or eatspace" in
+  let redo_spaces prev = function
+      Cocci2(s,line,lcol,rcol,Some (Unparse_cocci.SpaceOrNewline sp)) ->
+        C2 !sp :: Cocci2(s,line,lcol,rcol,None) :: prev
+    | t -> t::prev in
+  (match !Flag_parsing_c.spacing with
+    Flag_parsing_c.SMPL -> toks
+  | _ -> List.rev (List.fold_left redo_spaces [] (loop ([],None) 0 toks)))
 
 (* When insert some new code, because of a + in a SP, we must add this
  * code at the right place, with the good indentation. So each time we
@@ -791,7 +998,7 @@ let new_tabbing a =
 
 let rec adjust_indentation xs =
 
-  let _current_tabbing = ref "" in
+  let _current_tabbing = ref ([] : string list) in
   let tabbing_unit = ref None in
 
   let string_of_list l = String.concat "" (List.map string_of_char l) in
@@ -809,15 +1016,18 @@ let rec adjust_indentation xs =
        | (o::os,n::ns) -> loop (os,ns) in (* could check for equality *)
       loop (old_tab,new_tab) in
 
+(*
   let remtab tu current_tab =
     let current_tab = List.rev(list_of_string current_tab) in
     let rec loop = function
        ([],new_tab) -> string_of_list (List.rev new_tab)
-      |        (_,[]) -> "" (*weird; tabbing unit used up more than the current tab*)
+      |        (_,[]) -> (-*weird; tabbing unit used up more than the current tab*-)
+        ""
       |        (t::ts,n::ns) when t =<= n -> loop (ts,ns)
-      |        (_,ns) -> (* mismatch; remove what we can *)
+      |        (_,ns) -> (-* mismatch; remove what we can *-)
          string_of_list (List.rev ns) in
     loop (tu,current_tab) in
+*)
 
   let rec find_first_tab started = function
       [] -> ()
@@ -831,57 +1041,86 @@ let rec adjust_indentation xs =
     | x::xs -> find_first_tab started xs in
   find_first_tab false xs;
 
+  let rec balanced ct = function
+      [] -> ct >= 0
+    | ((T2(tok,_,_)) as x)::xs ->
+       (match str_of_token2 x with
+         "(" -> balanced (ct+1) xs
+       | ")" -> balanced (ct-1) xs
+       | _ -> balanced ct xs)
+    | x::xs -> balanced ct xs in
+
+  let update_tabbing started s x =
+    let old_tabbing = !_current_tabbing in
+    str_of_token2 x +> new_tabbing +> (fun s -> _current_tabbing := [s]);
+    (* only trust the indentation after the first { *)
+    if started
+    then
+      adjust_tabbing_unit
+       (String.concat "" old_tabbing)
+       (String.concat "" !_current_tabbing) in
+
   let rec aux started xs =
     match xs with
     | [] ->  []
 (* patch: coccinelle *)
+    | ((T2 (Parser_c.TCommentNewline s,_,_)) as x)::
+      Unindent_cocci2(false)::xs ->
+       update_tabbing started s x;
+        (C2 "\n")::aux started xs
+    | (Cocci2("\n",_,_,_,_))::Unindent_cocci2(false)::xs ->
+        (C2 "\n")::aux started xs
     | ((T2 (tok,_,_)) as x)::(T2 (Parser_c.TCommentNewline s, _, _))::
-      ((Cocci2 ("{",_,_,_)) as a)::xs
+      ((Cocci2 ("{",_,_,_,_)) as a)::xs
       when started && str_of_token2 x =$= ")" ->
        (* to be done for if, etc, but not for a function header *)
        x::(C2 " ")::a::(aux started xs)
-    | ((T2 (Parser_c.TCommentNewline s, _, _)) as x)::xs ->
-       let old_tabbing = !_current_tabbing in
-        str_of_token2 x +> new_tabbing +> (fun s -> _current_tabbing := s);
-       (* only trust the indentation after the first { *)
-       (if started
-       then adjust_tabbing_unit old_tabbing !_current_tabbing);
+    | ((T2 (Parser_c.TCommentNewline s, _, _)) as x)::xs
+      when
+       balanced 0 (fst(Common.span (function x -> not(is_newline x)) xs)) ->
+       update_tabbing started s x;
        let coccis_rest = Common.span all_coccis xs in
        (match coccis_rest with
          (_::_,((T2 (tok,_,_)) as y)::_) when str_of_token2 y =$= "}" ->
            (* the case where cocci code has been added before a close } *)
            x::aux started (Indent_cocci2::xs)
         | _ -> x::aux started xs)
+    | Indent_cocci2::((Cocci2(sy,lny,lcoly,_,_)) as y)::xs
+      when !Flag_parsing_c.spacing = Flag_parsing_c.SMPL ->
+       let tu = String.make (lcoly-1) ' ' in
+       _current_tabbing := tu::(!_current_tabbing);
+       C2 (tu)::aux started (y::xs)
     | Indent_cocci2::xs ->
        (match !tabbing_unit with
          None -> aux started xs
        | Some (tu,_) ->
-           _current_tabbing := (!_current_tabbing)^tu;
-           Cocci2 (tu,-1,-1,-1)::aux started xs)
+           _current_tabbing := tu::(!_current_tabbing);
+            (* can't be C2, for later phases *)
+            Cocci2 (tu,-1,-1,-1,None)::aux started xs)
     | Unindent_cocci2(permanent)::xs ->
-       (match !tabbing_unit with
-         None -> aux started xs
-       | Some (_,tu) ->
-           _current_tabbing := remtab tu (!_current_tabbing);
-           aux started xs)
+       (match !_current_tabbing with
+         [] -> aux started xs
+       | _::new_tabbing ->
+            let s = String.concat "" new_tabbing in
+           _current_tabbing := new_tabbing;
+           Cocci2 (s,-1,-1,-1,None)::aux started xs)
     (* border between existing code and cocci code *)
-    | ((T2 (tok,_,_)) as x)::((Cocci2("\n",_,_,_)) as y)::xs
+    | ((T2 (tok,_,_)) as x)::((Cocci2("\n",_,_,_,_)) as y)::xs
       when str_of_token2 x =$= "{" ->
        x::aux true (y::Indent_cocci2::xs)
     | ((Cocci2 _) as x)::((T2 (tok,_,_)) as y)::xs
       when str_of_token2 y =$= "}" ->
-       x::aux started (y::Unindent_cocci2 true::xs)
+       x::aux started (Unindent_cocci2 true::y::xs)
     (* starting the body of the function *)
     | ((T2 (tok,_,_)) as x)::xs when str_of_token2 x =$= "{" ->  x::aux true xs
-    | ((Cocci2("{",_,_,_)) as a)::xs -> a::aux true xs
-    | ((Cocci2("\n",_,_,_)) as x)::Unindent_cocci2(false)::xs ->
-        x::aux started xs
-    | ((Cocci2("\n",_,_,_)) as x)::xs ->
+    | ((Cocci2("{",_,_,_,_)) as a)::xs -> a::aux true xs
+    | ((Cocci2("\n",_,_,_,_)) as x)::xs ->
             (* dont inline in expr because of weird eval order of ocaml *)
-        let s = !_current_tabbing in
-        x::Cocci2 (s,-1,-1,-1)::aux started xs
+        let s = String.concat "" !_current_tabbing in
+        (* can't be C2, for later phases *)
+        x::Cocci2 (s,-1,-1,-1,None)::aux started xs
     | x::xs -> x::aux started xs in
-  aux false xs
+  (aux false xs,!tabbing_unit)
 
 
 let rec find_paren_comma = function
@@ -938,9 +1177,10 @@ let fix_tokens toks =
 type kind_token2 = KFake | KCocci | KC | KExpanded | KOrigin
 
 let kind_of_token2 = function
-  | Fake2 -> KFake
+  | Fake2 -> KFake
   | Cocci2 _ -> KCocci
   | C2 _ -> KC
+  | Comma _ -> KC
   | T2 (t,_,_) ->
       (match TH.pinfo_of_tok t with
       | ExpandedTok _ -> KExpanded
@@ -948,7 +1188,7 @@ let kind_of_token2 = function
       | FakeTok _ -> raise Impossible (* now a Fake2 *)
       | AbstractLineTok _ -> raise Impossible (* now a KC *)
       )
-  | Unindent_cocci2 _ | Indent_cocci2 -> raise Impossible
+  | Unindent_cocci2 _ | Indent_cocci2 | EatSpace2 -> raise Impossible
 
 let end_mark = "!"
 
@@ -1031,7 +1271,6 @@ let pp_program2 xs outfile  =
       match ppmethod with
       | PPnormal ->
           (* now work on tokens *)
-
           (* phase1: just get all the tokens, all the information *)
           assert(toks_e +> List.for_all (fun t ->
            TH.is_origin t or TH.is_expanded t
@@ -1040,21 +1279,31 @@ let pp_program2 xs outfile  =
          let toks = displace_fake_nodes toks in
           (* assert Origin;ExpandedTok;Faketok *)
           let toks = expand_mcode toks in
+
           (* assert Origin;ExpandedTok; + Cocci + C (was AbstractLineTok)
            * and no tag information, just NOTHING. *)
 
          let toks =
            if !Flag.sgrep_mode2
-           then drop_minus toks (* nothing to do for sgrep *)
+           then
+             (* nothing else to do for sgrep *)
+             drop_expanded(drop_fake(drop_minus toks))
            else
               (* phase2: can now start to filter and adjust *)
-              let toks = adjust_indentation toks in
+              (let (toks,tu) = adjust_indentation toks in
+             let toks = adjust_eat_space toks in
              let toks = adjust_before_semicolon toks in(*before remove minus*)
+             let toks = adjust_after_paren toks in(*also before remove minus*)
+             let toks = drop_space_at_endline toks in
+             let toks = paren_to_space toks in
+             let toks = drop_end_comma toks in
               let toks = remove_minus_and_between_and_expanded_and_fake toks in
               (* assert Origin + Cocci + C and no minus *)
               let toks = add_space toks in
+             let toks = add_newlines toks tu in
+             let toks = paren_then_brace toks in
               let toks = fix_tokens toks in
-             toks in
+              toks) in
 
           (* in theory here could reparse and rework the ast! or
            * apply some SP. Not before cos julia may have generated