~ubuntu-branches/ubuntu/oneiric/haxe/oneiric

« back to all changes in this revision

Viewing changes to ocaml/swflib/as3parse.ml

  • Committer: Bazaar Package Importer
  • Author(s): Jens Peter Secher
  • Date: 2009-03-18 23:09:50 UTC
  • mfrom: (3.1.1 experimental)
  • Revision ID: james.westby@ubuntu.com-20090318230950-pgfuxg2ucolps74t
Tags: 1:2.2-2
* Use ocamlfind to locate and use the libraries xml-light and extlib
  which already exist in Debian as separate packages.
  (Closes: #519630)
* Fixed compile error with camlp4 3.11, thanks to Stéphane Glondu.
  (Closes: #519627)
* Use quilt instead of dpatch for patches, and describe how to use
  quilt in Debian.source (thanks to Russ Allbery).
* Added a Vcs-Hg control filed to indicate the location of the public
  repository.
* Bumped Standards-Version to 3.8.1.

Show diffs side-by-side

added added

removed removed

Lines of Context:
86
86
        else
87
87
                1
88
88
 
 
89
let as3_uint_length i =
 
90
        as3_int_length i
 
91
 
89
92
let sum f l =
90
93
        List.fold_left (fun acc n -> acc + f n) 0 l
91
94
 
136
139
                idx_length idx
137
140
        | A3MAttrib n ->
138
141
                as3_name_length n - 1
 
142
        | A3MParams (id,pl) ->
 
143
                idx_length id + 1 + (sum idx_length pl)
139
144
 
140
145
let as3_value_length extra = function
141
146
        | A3VNone -> if extra then 2 else 1
222
227
        String.length ctx.as3_unknown +
223
228
        4 +
224
229
        list_length as3_int_length ctx.as3_ints +
225
 
        1 +
 
230
        list_length as3_uint_length ctx.as3_uints +
226
231
        list_length (fun _ -> 8) ctx.as3_floats
227
232
        + if parse_idents then list_length as3_ident_length ctx.as3_idents
228
233
        + if parse_namespaces then list_length (as3_namespace_length ei) ctx.as3_namespaces
267
272
        Int32.logor big small
268
273
 
269
274
let read_as3_uint ch =
270
 
        assert false
 
275
        read_as3_int ch
271
276
 
272
277
let read_int ch =
273
278
        Int32.to_int (read_as3_int ch)
348
353
                A3MMultiNameLate ns
349
354
        | 0x1C ->
350
355
                A3MAttrib (read_name ctx ~k:0x1B ch)
 
356
        | 0x1D ->
 
357
                let rec loop n =
 
358
                        if n = 0 then
 
359
                                []
 
360
                        else
 
361
                                let name = magic_index (read_int ch) in
 
362
                                name :: loop (n - 1)
 
363
                in
 
364
                let id = magic_index (read_int ch) in
 
365
                A3MParams (id,loop (IO.read_byte ch))
351
366
        | n ->
 
367
                prerr_endline (string_of_int n);
352
368
                assert false
353
369
 
354
370
let read_value ctx ch extra =
688
704
                        | A3MRuntimeName _ -> 0x10
689
705
                        | A3MRuntimeNameLate -> 0x12
690
706
                        | A3MMultiNameLate _ -> 0x1C
691
 
                        | A3MAttrib _ -> assert false
 
707
                        | A3MAttrib _ | A3MParams _ -> assert false
692
708
                ) n
 
709
        | A3MParams (id,pl) ->
 
710
                IO.write_byte ch (b 0x1D);
 
711
                write_index ch id;
 
712
                IO.write_byte ch (List.length pl);
 
713
                List.iter (write_index ch) pl
693
714
 
694
715
let write_value ch extra v =
695
716
        match v with
854
875
(* ************************************************************************ *)
855
876
(* DUMP *)
856
877
 
 
878
let dump_code_size = ref true
 
879
 
857
880
let ident_str ctx i =
858
881
        iget ctx.as3_idents i
859
882
 
875
898
        let l = iget ctx.as3_nsets i in
876
899
        String.concat " " (List.map (fun r -> namespace_str ctx r) l)
877
900
 
878
 
let name_str ctx kind t =
 
901
let rec name_str ctx kind t =
879
902
        let rec loop = function
880
903
                | A3MName (id,r) -> Printf.sprintf "%s %s%s" (namespace_str ctx r) kind (ident_str ctx id)
881
904
                | A3MMultiName (id,r) -> Printf.sprintf "[%s %s%s]" (ns_set_str ctx r) kind (match id with None -> "NO" | Some i -> ident_str ctx i)
883
906
                | A3MRuntimeNameLate -> "RTLATE"
884
907
                | A3MMultiNameLate id -> Printf.sprintf "late:(%s)" (ns_set_str ctx id)
885
908
                | A3MAttrib n -> "attrib " ^ loop n
 
909
                | A3MParams (id,pl) -> Printf.sprintf "%s<%s>" (name_str ctx kind id) (String.concat "," (List.map (name_str ctx kind) pl))
886
910
        in
887
911
        loop (iget ctx.as3_names t)
888
912
 
1008
1032
        let pos = ref 0 in
1009
1033
        Array.iter (fun op ->
1010
1034
                IO.printf ch "%4d    %s\n" !pos (As3code.dump ctx op);
1011
 
                pos := !pos + As3code.length op;
 
1035
                if !dump_code_size then pos := !pos + As3code.length op else incr pos;
1012
1036
        ) f.fun3_code;
1013
1037
        IO.printf ch "\n"
1014
1038
 
1040
1064
        (match id with
1041
1065
        | None -> IO.printf ch "\n---------------- AS3 -------------------------\n\n";
1042
1066
        | Some (id,f) -> IO.printf ch "\n---------------- AS3 %s [%d] -----------------\n\n" f id);
1043
 
        Array.iteri (dump_int ctx ch) ctx.as3_ints;
 
1067
(*      Array.iteri (dump_int ctx ch) ctx.as3_ints;
1044
1068
        Array.iteri (dump_float ctx ch) ctx.as3_floats;
1045
1069
        Array.iteri (dump_ident ctx ch) ctx.as3_idents;
1046
1070
        IO.printf ch "\n";
1049
1073
        Array.iteri (dump_ns_set ctx ch) ctx.as3_nsets;
1050
1074
        IO.printf ch "\n";
1051
1075
        Array.iteri (dump_name ctx ch) ctx.as3_names;
1052
 
        IO.printf ch "\n";
 
1076
        IO.printf ch "\n"; *)
1053
1077
(*      Array.iteri (dump_metadata ctx ch) ctx.as3_metadatas; *)
1054
1078
        Array.iteri (dump_class ctx ch) ctx.as3_classes;
1055
1079
        Array.iteri (dump_init ctx ch) ctx.as3_inits;