diff --git a/.Makefile.lint b/.Makefile.lint
index c74c7c5be984e086ae376f259a784e7374c0f3e5..a46b10f034d31648886220a4a83163f8248969e7 100644
--- a/.Makefile.lint
+++ b/.Makefile.lint
@@ -325,7 +325,6 @@ ML_LINT_KO+=src/plugins/metrics/metrics_parameters.ml
 ML_LINT_KO+=src/plugins/metrics/register.ml
 ML_LINT_KO+=src/plugins/metrics/register_gui.ml
 ML_LINT_KO+=src/plugins/obfuscator/dictionary.ml
-ML_LINT_KO+=src/plugins/obfuscator/obfuscate.ml
 ML_LINT_KO+=src/plugins/obfuscator/obfuscator_kind.ml
 ML_LINT_KO+=src/plugins/obfuscator/obfuscator_register.ml
 ML_LINT_KO+=src/plugins/obfuscator/options.ml
diff --git a/src/plugins/obfuscator/obfuscate.ml b/src/plugins/obfuscator/obfuscate.ml
index eba13df113289c5ff7af436f389ed2843477968e..5b6799903acaa869ff816152cb3feec33fb8aa8a 100644
--- a/src/plugins/obfuscator/obfuscate.ml
+++ b/src/plugins/obfuscator/obfuscate.ml
@@ -23,7 +23,7 @@
 open Cil_types
 open Cil_datatype
 
-let warn kind name = 
+let warn kind name =
   Options.warning ~once:true "unobfuscated %s name `%s'" kind name
 
 let has_literal_string = ref false
@@ -37,43 +37,43 @@ class visitor = object
   val id_pred_visited = Identified_predicate.Hashtbl.create 7
 
   method! vglob_aux = function
-  | GType (ty,_) ->
-    if not (Cil.typeHasAttribute "fc_stdlib" ty.ttype) then
-      ty.tname <- Dictionary.fresh Obfuscator_kind.Type ty.tname;
-    Cil.DoChildren
-  | GVarDecl (v, _) | GVar (v, _, _) | GFun ({svar = v}, _) | GFunDecl (_, v, _)
+    | GType (ty,_) ->
+      if not (Cil.typeHasAttribute "fc_stdlib" ty.ttype) then
+        ty.tname <- Dictionary.fresh Obfuscator_kind.Type ty.tname;
+      Cil.DoChildren
+    | GVarDecl (v, _) | GVar (v, _, _) | GFun ({svar = v}, _) | GFunDecl (_, v, _)
       when Cil.is_unused_builtin v ->
-    Cil.SkipChildren
-  | _ ->
-    Cil.DoChildren
+      Cil.SkipChildren
+    | _ ->
+      Cil.DoChildren
 
-  method! vcompinfo ci =  
-    ci.cname <- Dictionary.fresh Obfuscator_kind.Type ci.cname; 
+  method! vcompinfo ci =
+    ci.cname <- Dictionary.fresh Obfuscator_kind.Type ci.cname;
     Cil.DoChildren
 
-  method! venuminfo ei = 
-    ei.ename <- Dictionary.fresh Obfuscator_kind.Type ei.ename; 
+  method! venuminfo ei =
+    ei.ename <- Dictionary.fresh Obfuscator_kind.Type ei.ename;
     Cil.DoChildren
 
   method! vfieldinfo fi =
-    fi.fname <- Dictionary.fresh Obfuscator_kind.Field fi.fname; 
+    fi.fname <- Dictionary.fresh Obfuscator_kind.Field fi.fname;
     Cil.DoChildren
 
-  method! venumitem ei = 
-    ei.einame <- Dictionary.fresh Obfuscator_kind.Enum ei.einame; 
+  method! venumitem ei =
+    ei.einame <- Dictionary.fresh Obfuscator_kind.Enum ei.einame;
     Cil.DoChildren
 
   method! vexpr e = match e.enode with
-  | Const(CStr str) -> 
-    has_literal_string := true;
-    (* ignore the result: will be handle by hacking the pretty printer *)
-    (try
-       ignore (Dictionary.id_of_literal_string str)
-     with Not_found -> 
-       ignore (Dictionary.fresh Obfuscator_kind.Literal_string str));
-    Cil.SkipChildren
-  | _ -> 
-    Cil.DoChildren
+    | Const(CStr str) ->
+      has_literal_string := true;
+      (* ignore the result: will be handle by hacking the pretty printer *)
+      (try
+         ignore (Dictionary.id_of_literal_string str)
+       with Not_found ->
+         ignore (Dictionary.fresh Obfuscator_kind.Literal_string str));
+      Cil.SkipChildren
+    | _ ->
+      Cil.DoChildren
 
   method! vvdec vi =
     (* Varinfo can be visited (and obfuscated) more than once:
@@ -92,11 +92,11 @@ class visitor = object
           vi.vname <- Dictionary.fresh Obfuscator_kind.Function vi.vname
       end
       else begin
-	let add =
+        let add =
           if vi.vglob then Dictionary.fresh Obfuscator_kind.Global_var
           else if vi.vformal then Dictionary.fresh Obfuscator_kind.Formal_var
           else Dictionary.fresh Obfuscator_kind.Local_var
-	in
+        in
         vi.vname <- add vi.vname;
       end;
       Varinfo.Hashtbl.add varinfos_visited vi ();
@@ -107,25 +107,25 @@ class visitor = object
     match lvi.lv_kind with
     | LVGlobal | LVFormal | LVQuant | LVLocal ->
       if Logic_var.Hashtbl.mem logic_vars_visited lvi then
-	Cil.SkipChildren
+        Cil.SkipChildren
       else begin
-	lvi.lv_name <- Dictionary.fresh Obfuscator_kind.Logic_var lvi.lv_name;
-	Logic_var.Hashtbl.add logic_vars_visited lvi ();
-	Cil.DoChildren
+        lvi.lv_name <- Dictionary.fresh Obfuscator_kind.Logic_var lvi.lv_name;
+        Logic_var.Hashtbl.add logic_vars_visited lvi ();
+        Cil.DoChildren
       end
-    | LVC -> 
+    | LVC ->
       Cil.SkipChildren
 
   method! vstmt_aux stmt =
-    let labels = 
+    let labels =
       List.map
-	(function
-	| Label(s, loc, true) -> 
-	  (* only obfuscate user's labels, not Cil's ones *)
-	  let s' = Dictionary.fresh Obfuscator_kind.Label s in
-	  Label(s', loc, true)
-	| Label(_, _, false) | Case _ | Default _ as label -> label)
-	stmt.labels
+        (function
+          | Label(s, loc, true) ->
+            (* only obfuscate user's labels, not Cil's ones *)
+            let s' = Dictionary.fresh Obfuscator_kind.Label s in
+            Label(s', loc, true)
+          | Label(_, _, false) | Case _ | Default _ as label -> label)
+        stmt.labels
     in
     stmt.labels <- labels;
     Cil.DoChildren
@@ -143,21 +143,21 @@ class visitor = object
       Cil.ChangeDoChildrenPost (p', Extlib.id)
     end
 
-  method! vterm t = 
+  method! vterm t =
     List.iter (fun s -> warn "term" s) t.term_name;
     Cil.DoChildren
 
   method! vannotation = function
-  | Daxiomatic(str, _, _, _) ->
-    warn "axiomatic" str;
-    Cil.DoChildren
-  | Dlemma(str, axiom, _, _, _, _, _) ->
-    warn (if axiom then "axiom" else "lemma") str;
-    Cil.DoChildren
-  | _ -> 
-    Cil.DoChildren
+    | Daxiomatic(str, _, _, _) ->
+      warn "axiomatic" str;
+      Cil.DoChildren
+    | Dlemma(str, axiom, _, _, _, _, _) ->
+      warn (if axiom then "axiom" else "lemma") str;
+      Cil.DoChildren
+    | _ ->
+      Cil.DoChildren
 
-  method! vmodel_info mi = 
+  method! vmodel_info mi =
     warn "model" mi.mi_name;
     Cil.DoChildren
 
@@ -174,14 +174,14 @@ class visitor = object
     Cil.DoChildren
 
   method! vattr = function
-  | Attr(str, _) | AttrAnnot str -> 
-    warn "attribute" str; 
-    Cil.DoChildren
+    | Attr(str, _) | AttrAnnot str ->
+      warn "attribute" str;
+      Cil.DoChildren
 
-  method! vattrparam p = 
+  method! vattrparam p =
     (match p with
-    | AStr str | ACons(str, _) | ADot(_, str) -> warn "attribute parameter" str
-    | _ -> ());
+     | AStr str | ACons(str, _) | ADot(_, str) -> warn "attribute parameter" str
+     | _ -> ());
     Cil.DoChildren
 
   initializer has_literal_string := false
@@ -192,79 +192,79 @@ let obfuscate_behaviors () =
   (* inheriting method vbehavior or vspec does not work since only a copy of the
      piece of spec is provided. *)
   Globals.Functions.iter
-    (fun kf -> 
-      let h = Datatype.String.Hashtbl.create 7 in
-      Annotations.iter_behaviors
-	(fun emitter b -> 
-	  if Emitter.equal emitter Emitter.end_user 
-	    && not (Cil.is_default_behavior b)
-	  then begin
-	    Annotations.remove_behavior ~force:true emitter kf b;
-	    let new_ = Dictionary.fresh Obfuscator_kind.Behavior b.b_name in
-	    Datatype.String.Hashtbl.add h b.b_name new_;
-	    b.b_name <- new_;
-	    Annotations.add_behaviors emitter kf [ b ];
-	  end)
-	kf;
-      let handle_bnames iter remove add =
-	iter
-	  (fun emitter l ->
-	    remove emitter kf l;
-	    add emitter kf (List.map (Datatype.String.Hashtbl.find h) l))
-	  kf
-      in
-      handle_bnames
-	Annotations.iter_complete
-	(fun e kf l -> Annotations.remove_complete e kf l)
-	(fun e kf l -> Annotations.add_complete e kf l);
-      handle_bnames 
-	Annotations.iter_disjoint
-	(fun e kf l -> Annotations.remove_disjoint e kf l)
-	(fun e kf l -> Annotations.add_disjoint e kf l))
+    (fun kf ->
+       let h = Datatype.String.Hashtbl.create 7 in
+       Annotations.iter_behaviors
+         (fun emitter b ->
+            if Emitter.equal emitter Emitter.end_user
+            && not (Cil.is_default_behavior b)
+            then begin
+              Annotations.remove_behavior ~force:true emitter kf b;
+              let new_ = Dictionary.fresh Obfuscator_kind.Behavior b.b_name in
+              Datatype.String.Hashtbl.add h b.b_name new_;
+              b.b_name <- new_;
+              Annotations.add_behaviors emitter kf [ b ];
+            end)
+         kf;
+       let handle_bnames iter remove add =
+         iter
+           (fun emitter l ->
+              remove emitter kf l;
+              add emitter kf (List.map (Datatype.String.Hashtbl.find h) l))
+           kf
+       in
+       handle_bnames
+         Annotations.iter_complete
+         (fun e kf l -> Annotations.remove_complete e kf l)
+         (fun e kf l -> Annotations.add_complete e kf l);
+       handle_bnames
+         Annotations.iter_disjoint
+         (fun e kf l -> Annotations.remove_disjoint e kf l)
+         (fun e kf l -> Annotations.add_disjoint e kf l))
 
 module UpdatePrinter (X: Printer.PrinterClass) = struct
-(* obfuscated printer *)
-class printer = object
-  inherit X.printer as super
-  method! constant fmt = function
-  | CStr str -> Format.fprintf fmt "%s" (Dictionary.id_of_literal_string str)
-  | c -> super#constant fmt c
+  (* obfuscated printer *)
+  class printer = object
+    inherit X.printer as super
+    method! constant fmt = function
+      | CStr str -> Format.fprintf fmt "%s" (Dictionary.id_of_literal_string str)
+      | c -> super#constant fmt c
 
-  method! file fmt ast =
-    if !has_literal_string then begin
-      let string_fmt =
-	if Options.Literal_string.is_default () then fmt
-	else begin
-	  let file = Options.Literal_string.get () in
-	  try
-	    let cout = open_out file in
-	    Format.formatter_of_out_channel cout
-	  with Sys_error _ as exn ->
-	    Options.error "@[cannot generate the literal string dictionary \
-into file `%s':@ %s@]"
-	      file
-	      (Printexc.to_string exn);
-	    fmt
-	end
-      in
-      Format.fprintf string_fmt "\
+    method! file fmt ast =
+      if !has_literal_string then begin
+        let string_fmt =
+          if Options.Literal_string.is_default () then fmt
+          else begin
+            let file = Options.Literal_string.get () in
+            try
+              let cout = open_out file in
+              Format.formatter_of_out_channel cout
+            with Sys_error _ as exn ->
+              Options.error "@[cannot generate the literal string dictionary \
+                             into file `%s':@ %s@]"
+                file
+                (Printexc.to_string exn);
+              fmt
+          end
+        in
+        Format.fprintf string_fmt "\
 /* *********************************************************** */@\n\
 /* start of dictionary required to compile the obfuscated code */@\n\
 /* *********************************************************** */@\n";
-      Dictionary.pretty_kind string_fmt Obfuscator_kind.Literal_string;
-      Format.fprintf string_fmt "\
+        Dictionary.pretty_kind string_fmt Obfuscator_kind.Literal_string;
+        Format.fprintf string_fmt "\
 /* ********************************************************* */@\n\
 /* end of dictionary required to compile the obfuscated code */@\n\
 /* ********************************************************* */@\n@\n";
-      if fmt != string_fmt then begin
-	Format.pp_print_flush string_fmt ();
-	Format.fprintf fmt "\
+        if fmt != string_fmt then begin
+          Format.pp_print_flush string_fmt ();
+          Format.fprintf fmt "\
 /* include the dictionary of literal strings */@\n\
-@[#include \"%s\"@]@\n@\n" 
-	  (Options.Literal_string.get ())
-      end
-    end;
-    super#file fmt ast
+@[#include \"%s\"@]@\n@\n"
+            (Options.Literal_string.get ())
+        end
+      end;
+      super#file fmt ast
 
   end
 end
@@ -272,8 +272,8 @@ end
 let obfuscate () =
   Dictionary.mark_as_computed ();
   obfuscate_behaviors ();
-  Visitor.visitFramacFileSameGlobals 
-    (new visitor :> Visitor.frama_c_visitor) 
+  Visitor.visitFramacFileSameGlobals
+    (new visitor :> Visitor.frama_c_visitor)
     (Ast.get ());
   Printer.update_printer (module UpdatePrinter: Printer.PrinterExtension)