Thrift: Whitespace cleanup.

Summary:
- Expanded tabs to spaces where spaces were the norm.
- Deleted almost all trailing whitespace.
- Added newlines to the ends of a few files.
- Ran dos2unix on one file or two.

Reviewed By: mcslee

Test Plan: git diff -b

Revert Plan: ok


git-svn-id: https://svn.apache.org/repos/asf/incubator/thrift/trunk@665467 13f79535-47bb-0310-9956-ffa450edef68
diff --git a/lib/ocaml/src/TBinaryProtocol.ml b/lib/ocaml/src/TBinaryProtocol.ml
index fa84e71..109eeaa 100644
--- a/lib/ocaml/src/TBinaryProtocol.ml
+++ b/lib/ocaml/src/TBinaryProtocol.ml
@@ -10,7 +10,7 @@
 let vt = P.t_type_of_i
 
 
-let comp_int b n = 
+let comp_int b n =
   let s = ref 0l in
   let sb = 32 - 8*n in
     for i=0 to (n-1) do
@@ -32,7 +32,7 @@
 object (self)
   inherit P.t trans
   val ibyte = String.create 8
-  method writeBool b = 
+  method writeBool b =
     ibyte.[0] <- char_of_int (if b then 1 else 0);
     trans#write ibyte 0 1
   method writeByte i =
@@ -88,7 +88,7 @@
     self#writeByte (tv t);
     self#writeI32 s
   method writeSetEnd = ()
-  method readByte = 
+  method readByte =
     ignore (trans#readAll ibyte 0 1);
     (comp_int ibyte 1)
   method readI16 =
@@ -124,7 +124,7 @@
     ""
   method readStructEnd = ()
   method readFieldBegin =
-    let t = (vt (self#readByte)) 
+    let t = (vt (self#readByte))
     in
       if t != P.T_STOP then
         ("",t,self#readI16)
diff --git a/lib/ocaml/src/TChannelTransport.ml b/lib/ocaml/src/TChannelTransport.ml
index 5407a8e..9678e5a 100644
--- a/lib/ocaml/src/TChannelTransport.ml
+++ b/lib/ocaml/src/TChannelTransport.ml
@@ -8,12 +8,12 @@
   method isOpen = opened
   method opn = ()
   method close = close_in i; opened <- false
-  method read buf off len = 
+  method read buf off len =
     if opened then
-      try 
+      try
         really_input i buf off len; len
       with _ -> raise (T.E (T.UNKNOWN, ("TChannelTransport: Could not read "^(string_of_int len))))
-    else 
+    else
       raise (T.E (T.NOT_OPEN, "TChannelTransport: Channel was closed"))
   method write buf off len = output o buf off len
   method flush = flush o
diff --git a/lib/ocaml/src/TServer.ml b/lib/ocaml/src/TServer.ml
index 5fb8089..bd97ab9 100644
--- a/lib/ocaml/src/TServer.ml
+++ b/lib/ocaml/src/TServer.ml
@@ -1,7 +1,7 @@
 open Thrift
 
 class virtual t
-    (pf : Processor.t) 
+    (pf : Processor.t)
     (st : Transport.server_t)
     (tf : Transport.factory)
     (ipf : Protocol.factory)
diff --git a/lib/ocaml/src/TServerSocket.ml b/lib/ocaml/src/TServerSocket.ml
index 9e79706..1e82609 100644
--- a/lib/ocaml/src/TServerSocket.ml
+++ b/lib/ocaml/src/TServerSocket.ml
@@ -11,7 +11,7 @@
       Unix.listen s 256
   method close =
     match sock with
-        Some s -> Unix.shutdown s Unix.SHUTDOWN_ALL; Unix.close s; 
+        Some s -> Unix.shutdown s Unix.SHUTDOWN_ALL; Unix.close s;
           sock <- None
       | _ -> ()
   method acceptImpl =
diff --git a/lib/ocaml/src/TSocket.ml b/lib/ocaml/src/TSocket.ml
index 20c8613..2d82437 100644
--- a/lib/ocaml/src/TSocket.ml
+++ b/lib/ocaml/src/TSocket.ml
@@ -7,34 +7,34 @@
   inherit T.t
   val mutable chans = None
   method isOpen = chans != None
-  method opn = 
+  method opn =
     try
       let addr = (let {Unix.h_addr_list=x} = Unix.gethostbyname host in x.(0)) in
         chans <- Some(Unix.open_connection (Unix.ADDR_INET (addr,port)))
-    with 
+    with
         Unix.Unix_error (e,fn,_) -> raise (T.E (T.NOT_OPEN, ("TSocket: Could not connect to "^host^":"^(string_of_int port)^" because: "^fn^":"^(Unix.error_message e))))
       | _ -> raise (T.E (T.NOT_OPEN, ("TSocket: Could not connect to "^host^":"^(string_of_int port))))
 
-  method close = 
-    match chans with 
-        None -> () 
-      | Some(inc,out) -> (Unix.shutdown_connection inc; 
-                          close_in inc;  
+  method close =
+    match chans with
+        None -> ()
+      | Some(inc,out) -> (Unix.shutdown_connection inc;
+                          close_in inc;
                           chans <- None)
   method read buf off len = match chans with
       None -> raise (T.E (T.NOT_OPEN, "TSocket: Socket not open"))
-    | Some(i,o) -> 
-        try 
+    | Some(i,o) ->
+        try
           really_input i buf off len; len
         with
             Unix.Unix_error (e,fn,_) -> raise (T.E (T.UNKNOWN, ("TSocket: Could not read "^(string_of_int len)^" from "^host^":"^(string_of_int port)^" because: "^fn^":"^(Unix.error_message e))))
           | _ -> raise (T.E (T.UNKNOWN, ("TSocket: Could not read "^(string_of_int len)^" from "^host^":"^(string_of_int port))))
-  method write buf off len = match chans with 
+  method write buf off len = match chans with
       None -> raise (T.E (T.NOT_OPEN, "TSocket: Socket not open"))
     | Some(i,o) -> output o buf off len
   method flush = match chans with
       None -> raise (T.E (T.NOT_OPEN, "TSocket: Socket not open"))
     | Some(i,o) -> flush o
 end
-        
-    
+
+
diff --git a/lib/ocaml/src/TThreadedServer.ml b/lib/ocaml/src/TThreadedServer.ml
index 10f1614..702cb22 100644
--- a/lib/ocaml/src/TThreadedServer.ml
+++ b/lib/ocaml/src/TThreadedServer.ml
@@ -1,7 +1,7 @@
 open Thrift
 
-class t 
-  (pf : Processor.t) 
+class t
+  (pf : Processor.t)
   (st : Transport.server_t)
   (tf : Transport.factory)
   (ipf : Protocol.factory)
@@ -12,8 +12,8 @@
     st#listen;
     while true do
       let tr = tf#getTransport (st#accept) in
-        ignore (Thread.create 
-          (fun _ ->          
+        ignore (Thread.create
+          (fun _ ->
              let ip = ipf#getProtocol tr in
              let op = opf#getProtocol tr in
                try
@@ -23,4 +23,4 @@
                with _ -> ()) ())
     done
 end
-      
+
diff --git a/lib/ocaml/src/Thrift.ml b/lib/ocaml/src/Thrift.ml
index 92c015b..1a9130f 100644
--- a/lib/ocaml/src/Thrift.ml
+++ b/lib/ocaml/src/Thrift.ml
@@ -2,7 +2,7 @@
 exception Thrift_error;;
 exception Field_empty of string;;
 
-class t_exn = 
+class t_exn =
 object
   val mutable message = ""
   method get_message = message
@@ -11,7 +11,7 @@
 
 module Transport =
 struct
-  type exn_type = 
+  type exn_type =
       | UNKNOWN
       | NOT_OPEN
       | ALREADY_OPEN
@@ -52,31 +52,31 @@
     method virtual close : unit
     method virtual acceptImpl : t
   end
-        
+
 end;;
 
 
 
 module Protocol =
 struct
-  type t_type =   
-      | T_STOP     
-      | T_VOID     
+  type t_type =
+      | T_STOP
+      | T_VOID
       | T_BOOL
       | T_BYTE
-      | T_I08 
-      | T_I16 
-      | T_I32 
-      | T_U64 
-      | T_I64 
-      | T_DOUBLE 
-      | T_STRING 
-      | T_UTF7   
-      | T_STRUCT    
-      | T_MAP       
-      | T_SET       
-      | T_LIST      
-      | T_UTF8      
+      | T_I08
+      | T_I16
+      | T_I32
+      | T_U64
+      | T_I64
+      | T_DOUBLE
+      | T_STRING
+      | T_UTF7
+      | T_STRUCT
+      | T_MAP
+      | T_SET
+      | T_LIST
+      | T_UTF8
       | T_UTF16
 
   let t_type_to_i = function
@@ -98,25 +98,25 @@
     | T_LIST       -> 15
     | T_UTF8       -> 16
     | T_UTF16      -> 17
-        
+
   let t_type_of_i = function
-      0 -> T_STOP      
-    | 1 -> T_VOID      
+      0 -> T_STOP
+    | 1 -> T_VOID
     | 2 -> T_BOOL
     | 3 ->  T_BYTE
-    | 6-> T_I16       
-    | 8 -> T_I32      
-    | 9 -> T_U64      
-    | 10 -> T_I64     
-    | 4 -> T_DOUBLE   
+    | 6-> T_I16
+    | 8 -> T_I32
+    | 9 -> T_U64
+    | 10 -> T_I64
+    | 4 -> T_DOUBLE
     | 11 -> T_STRING
     | 12 -> T_STRUCT
-    | 13 -> T_MAP   
-    | 14 -> T_SET   
-    | 15 -> T_LIST  
-    | 16 -> T_UTF8  
+    | 13 -> T_MAP
+    | 14 -> T_SET
+    | 15 -> T_LIST
+    | 16 -> T_UTF8
     | 17 -> T_UTF16
-    | _ -> raise Thrift_error 
+    | _ -> raise Thrift_error
 
   type message_type =
     | CALL
@@ -128,7 +128,7 @@
     | REPLY -> 2
     | EXCEPTION -> 3
 
-  let message_type_of_i = function 
+  let message_type_of_i = function
     | 1 -> CALL
     | 2 -> REPLY
     | 3 -> EXCEPTION
@@ -182,7 +182,7 @@
     method virtual readString : string
     method virtual readBinary : string
         (* skippage *)
-    method skip typ = 
+    method skip typ =
       match typ with
         | T_STOP -> ()
         | T_VOID -> ()
@@ -192,7 +192,7 @@
         | T_I16 -> ignore self#readI16
         | T_I32 -> ignore self#readI32
         | T_U64
-        | T_I64 -> ignore self#readI64 
+        | T_I64 -> ignore self#readI64
         | T_DOUBLE -> ignore self#readDouble
         | T_STRING -> ignore self#readString
         | T_UTF7 -> ()
@@ -202,7 +202,7 @@
                                      let (_,t,_) = self#readFieldBegin in
                                        if t = T_STOP then
                                          raise Break
-                                       else 
+                                       else
                                          (self#skip t;
                                           self#readFieldEnd)
                                    done
@@ -241,8 +241,8 @@
       | BAD_VERSION
 
   exception E of exn_type * string;;
-           
-end;;   
+
+end;;
 
 
 module Processor =
@@ -251,10 +251,10 @@
   object
     method virtual process : Protocol.t -> Protocol.t -> bool
   end;;
-  
+
   class factory (processor : t) =
   object
-    val processor_ = processor 
+    val processor_ = processor
     method getProcessor (trans : Transport.t) = processor_
   end;;
 end
@@ -306,18 +306,18 @@
       oprot#writeFieldStop;
       oprot#writeStructEnd
   end;;
-  
+
   let create typ msg =
     let e = new t in
       e#set_type typ;
     e#set_message msg;
     e
-      
+
   let read (iprot : Protocol.t) =
     let msg = ref "" in
     let typ = ref 0 in
       ignore iprot#readStructBegin;
-      (try 
+      (try
            while true do
              let (name,ft,id) =iprot#readFieldBegin in
                if ft = Protocol.T_STOP then
@@ -341,6 +341,6 @@
         e#set_type (typ_of_i !typ);
         e#set_message !msg;
         e;;
-  
+
   exception E of t
 end;;