~ubuntu-branches/ubuntu/lucid/mtasc/lucid

« back to all changes in this revision

Viewing changes to ocaml/mtasc/typer.ml

  • Committer: Bazaar Package Importer
  • Author(s): Paul Wise
  • Date: 2007-05-23 19:17:16 UTC
  • mto: (2.1.1 gutsy)
  • mto: This revision was merged to the branch mainline in revision 3.
  • Revision ID: james.westby@ubuntu.com-20070523191716-lpvac307yorewp3g
Tags: upstream-1.13
ImportĀ upstreamĀ versionĀ 1.13

Show diffs side-by-side

added added

removed removed

Lines of Context:
557
557
and type_field ctx t f p =
558
558
        match resolve t f with
559
559
        | None -> 
560
 
                if not (is_dynamic t) then error (Custom (s_type_decl (match t with Static c -> Class c | _ -> t) ^ " have no " ^ (match t with Static _ -> "static " | _ -> "") ^ "field " ^ f)) p;
 
560
                if not (is_dynamic t) then error (Custom (s_type_decl (match t with Static c -> Class c | _ -> t) ^ " has no " ^ (match t with Static _ -> "static " | _ -> "") ^ "field " ^ f)) p;
561
561
                Dyn
562
562
        | Some f ->
563
563
                if f.f_public = IsPrivate then (match t with
736
736
let rec type_expr ctx (e,p) =
737
737
        match e with
738
738
        | EVars (_,_,vl) ->
739
 
                let vt = List.map (fun (name,tt,v) -> 
 
739
                List.iter (fun (name,tt,v) -> 
740
740
                        let t = (if !local_inference && v <> None && tt = None then Dyn else t_opt ctx p tt) in
741
741
                        let t = (match v with
742
742
                                | None -> t 
745
745
                                        unify_array tv t v (pos v);
746
746
                                        if !local_inference && tt = None then tv else t
747
747
                        ) in
748
 
                        name , t
749
 
                ) vl in
750
 
                List.iter (fun (name,t) -> define_local ctx name t p) vt
 
748
                        define_local ctx name t p                       
 
749
                ) vl
751
750
        | EFunction f ->
752
751
                assert false
753
752
        | EBlock el ->
839
838
                if not lambda then verbose_msg ("Typing " ^ s_type_path clctx.path ^ "." ^ f.fname);
840
839
                let ctx = {
841
840
                        ctx with
842
 
                                current = if lambda then { clctx with imports = ctx.current.imports } else clctx;
 
841
                                current = if lambda then { clctx with imports = ctx.current.imports; native = false; } else clctx;
843
842
                                locals = if lambda then ctx.locals else Hashtbl.create 0;
844
843
                                in_static = (f.fstatic = IsStatic);
845
844
                                in_constructor = (f.fstatic = IsMember && f.fname = clctx.name);
878
877
                let t = Function (List.map (fun (_,t) -> t_opt ctx p t) f.fargs , ret_opt ctx p f) in
879
878
                if f.fname = snd clctx.path then begin
880
879
                        if f.ftype <> None then error (Custom "Constructor return type should not be specified") p;
 
880
                        if clctx.interface then error (Custom "Interface can't have a constructor") p;
881
881
                        match clctx.constructor with
882
882
                        | None -> clctx.constructor <- Some { f_name = f.fname; f_type = t; f_static = IsMember; f_public = f.fpublic; f_pos = null_pos }
883
883
                        | Some _ -> error (Custom "Duplicate constructor") p;