src/Tools/Code/code_namespace.ML
author haftmann
Thu, 19 Apr 2012 10:16:51 +0200
changeset 48447 b32aae03e3d6
parent 45218 700008399ee5
child 53067 52fd62618631
permissions -rw-r--r--
dropped dead code;
tuned
     1 (*  Title:      Tools/Code/code_namespace.ML
     2     Author:     Florian Haftmann, TU Muenchen
     3 
     4 Mastering target language namespaces.
     5 *)
     6 
     7 signature CODE_NAMESPACE =
     8 sig
     9   type flat_program
    10   val flat_program: (string -> string) -> { module_alias: string -> string option,
    11     module_prefix: string, reserved: Name.context, empty_nsp: 'a,
    12     namify_stmt: Code_Thingol.stmt -> string -> 'a -> string * 'a,
    13     modify_stmt: Code_Thingol.stmt -> Code_Thingol.stmt option }
    14       -> Code_Thingol.program
    15       -> { deresolver: string -> string -> string,
    16            flat_program: flat_program }
    17 
    18   datatype ('a, 'b) node =
    19       Dummy
    20     | Stmt of 'a
    21     | Module of ('b * (string * ('a, 'b) node) Graph.T)
    22   type ('a, 'b) hierarchical_program
    23   val hierarchical_program: (string -> string) -> { module_alias: string -> string option,
    24     reserved: Name.context, empty_nsp: 'c, namify_module: string -> 'c -> string * 'c,
    25     namify_stmt: Code_Thingol.stmt -> string -> 'c -> string * 'c,
    26     cyclic_modules: bool, empty_data: 'b, memorize_data: string -> 'b -> 'b,
    27     modify_stmts: (string * Code_Thingol.stmt) list -> 'a option list }
    28       -> Code_Thingol.program
    29       -> { deresolver: string list -> string -> string,
    30            hierarchical_program: ('a, 'b) hierarchical_program }
    31   val print_hierarchical: { print_module: string list -> string -> 'b -> 'c list -> 'c,
    32     print_stmt: string list -> string * 'a -> 'c,
    33     lift_markup: (Pretty.T -> Pretty.T) -> 'c -> 'c }
    34       -> ('a, 'b) hierarchical_program -> 'c list
    35 end;
    36 
    37 structure Code_Namespace : CODE_NAMESPACE =
    38 struct
    39 
    40 (** building module name hierarchy **)
    41 
    42 val dest_name =
    43   apfst Long_Name.implode o split_last o fst o split_last o Long_Name.explode;
    44 
    45 fun build_module_namespace { module_alias, module_prefix, reserved } program =
    46   let
    47     fun alias_fragments name = case module_alias name
    48      of SOME name' => Long_Name.explode name'
    49       | NONE => map (fn name => fst (Name.variant name reserved)) (Long_Name.explode name);
    50     val module_names = Graph.fold (insert (op =) o fst o dest_name o fst) program [];
    51   in
    52     fold (fn name => Symtab.update (name, Long_Name.explode module_prefix @ alias_fragments name))
    53       module_names Symtab.empty
    54   end;
    55 
    56 
    57 (** flat program structure **)
    58 
    59 type flat_program = ((string * Code_Thingol.stmt option) Graph.T * (string * string list) list) Graph.T;
    60 
    61 fun flat_program labelled_name { module_alias, module_prefix, reserved,
    62       empty_nsp, namify_stmt, modify_stmt } program =
    63   let
    64 
    65     (* building module name hierarchy *)
    66     val fragments_tab = build_module_namespace { module_alias = module_alias,
    67       module_prefix = module_prefix, reserved = reserved } program;
    68     val dest_name = dest_name
    69       #>> (Long_Name.implode o the o Symtab.lookup fragments_tab);
    70 
    71     (* distribute statements over hierarchy *)
    72     fun add_stmt name stmt =
    73       let
    74         val (module_name, base) = dest_name name;
    75       in
    76         Graph.default_node (module_name, (Graph.empty, []))
    77         #> (Graph.map_node module_name o apfst) (Graph.new_node (name, (base, stmt)))
    78       end;
    79     fun add_dependency name name' =
    80       let
    81         val (module_name, _) = dest_name name;
    82         val (module_name', _) = dest_name name';
    83       in if module_name = module_name'
    84         then (Graph.map_node module_name o apfst) (Graph.add_edge (name, name'))
    85         else (Graph.map_node module_name o apsnd) (AList.map_default (op =) (module_name', []) (insert (op =) name'))
    86       end;
    87     val proto_program = Graph.empty
    88       |> Graph.fold (fn (name, (stmt, _)) => add_stmt name stmt) program
    89       |> Graph.fold (fn (name, (_, (_, names))) =>
    90           Graph.Keys.fold (add_dependency name) names) program;
    91 
    92     (* name declarations and statement modifications *)
    93     fun declare name (base, stmt) (gr, nsp) = 
    94       let
    95         val (base', nsp') = namify_stmt stmt base nsp;
    96         val gr' = (Graph.map_node name o apfst) (K base') gr;
    97       in (gr', nsp') end;
    98     fun declarations gr = (gr, empty_nsp)
    99       |> fold (fn name => declare name (Graph.get_node gr name)) (Graph.keys gr) 
   100       |> fst
   101       |> (Graph.map o K o apsnd) modify_stmt;
   102     val flat_program = proto_program
   103       |> (Graph.map o K o apfst) declarations;
   104 
   105     (* qualified and unqualified imports, deresolving *)
   106     fun base_deresolver name = fst (Graph.get_node
   107       (fst (Graph.get_node flat_program (fst (dest_name name)))) name);
   108     fun classify_names gr imports =
   109       let
   110         val import_tab = maps
   111           (fn (module_name, names) => map (rpair module_name) names) imports;
   112         val imported_names = map fst import_tab;
   113         val here_names = Graph.keys gr;
   114       in
   115         Symtab.empty
   116         |> fold (fn name => Symtab.update (name, base_deresolver name)) here_names
   117         |> fold (fn name => Symtab.update (name,
   118             Long_Name.append (the (AList.lookup (op =) import_tab name))
   119               (base_deresolver name))) imported_names
   120       end;
   121     val deresolver_tab = Symtab.make (AList.make
   122       (uncurry classify_names o Graph.get_node flat_program)
   123         (Graph.keys flat_program));
   124     fun deresolver "" name =
   125           Long_Name.append (fst (dest_name name)) (base_deresolver name)
   126       | deresolver module_name name =
   127           the (Symtab.lookup (the (Symtab.lookup deresolver_tab module_name)) name)
   128           handle Option => error ("Unknown statement name: " ^ labelled_name name);
   129 
   130   in { deresolver = deresolver, flat_program = flat_program } end;
   131 
   132 
   133 (** hierarchical program structure **)
   134 
   135 datatype ('a, 'b) node =
   136     Dummy
   137   | Stmt of 'a
   138   | Module of ('b * (string * ('a, 'b) node) Graph.T);
   139 
   140 type ('a, 'b) hierarchical_program = (string * ('a, 'b) node) Graph.T;
   141 
   142 fun map_module_content f (Module content) = Module (f content);
   143 
   144 fun map_module [] = I
   145   | map_module (name_fragment :: name_fragments) =
   146       apsnd o Graph.map_node name_fragment o apsnd o map_module_content
   147         o map_module name_fragments;
   148 
   149 fun hierarchical_program labelled_name { module_alias, reserved, empty_nsp,
   150       namify_module, namify_stmt, cyclic_modules, empty_data, memorize_data, modify_stmts } program =
   151   let
   152 
   153     (* building module name hierarchy *)
   154     val fragments_tab = build_module_namespace { module_alias = module_alias,
   155       module_prefix = "", reserved = reserved } program;
   156     val dest_name = dest_name #>> (the o Symtab.lookup fragments_tab);
   157 
   158     (* building empty module hierarchy *)
   159     val empty_module = (empty_data, Graph.empty);
   160     fun ensure_module name_fragment (data, nodes) =
   161       if can (Graph.get_node nodes) name_fragment then (data, nodes)
   162       else (data,
   163         nodes |> Graph.new_node (name_fragment, (name_fragment, Module empty_module)));
   164     fun allocate_module [] = I
   165       | allocate_module (name_fragment :: name_fragments) =
   166           ensure_module name_fragment
   167           #> (apsnd o Graph.map_node name_fragment o apsnd o map_module_content o allocate_module) name_fragments;
   168     val empty_program = Symtab.fold (fn (_, fragments) => allocate_module fragments)
   169       fragments_tab empty_module;
   170 
   171     (* distribute statements over hierarchy *)
   172     fun add_stmt name stmt =
   173       let
   174         val (name_fragments, base) = dest_name name;
   175       in
   176         (map_module name_fragments o apsnd) (Graph.new_node (name, (base, Stmt stmt)))
   177       end;
   178     fun add_dependency name name' =
   179       let
   180         val (name_fragments, _) = dest_name name;
   181         val (name_fragments', _) = dest_name name';
   182         val (name_fragments_common, (diff, diff')) =
   183           chop_prefix (op =) (name_fragments, name_fragments');
   184         val is_module = not (null diff andalso null diff');
   185         val dep = pairself hd (diff @ [name], diff' @ [name']);
   186         val add_edge = if is_module andalso not cyclic_modules
   187           then (fn node => Graph.add_edge_acyclic dep node
   188             handle Graph.CYCLES _ => error ("Dependency "
   189               ^ quote name ^ " -> " ^ quote name'
   190               ^ " would result in module dependency cycle"))
   191           else Graph.add_edge dep
   192       in (map_module name_fragments_common o apsnd) add_edge end;
   193     val proto_program = empty_program
   194       |> Graph.fold (fn (name, (stmt, _)) => add_stmt name stmt) program
   195       |> Graph.fold (fn (name, (_, (_, names))) =>
   196           Graph.Keys.fold (add_dependency name) names) program;
   197 
   198     (* name declarations, data and statement modifications *)
   199     fun make_declarations nsps (data, nodes) =
   200       let
   201         val (module_fragments, stmt_names) = List.partition
   202           (fn name_fragment => case Graph.get_node nodes name_fragment
   203             of (_, Module _) => true | _ => false) (Graph.keys nodes);
   204         fun declare namify name (nsps, nodes) =
   205           let
   206             val (base, node) = Graph.get_node nodes name;
   207             val (base', nsps') = namify node base nsps;
   208             val nodes' = Graph.map_node name (K (base', node)) nodes;
   209           in (nsps', nodes') end;
   210         val (nsps', nodes') = (nsps, nodes)
   211           |> fold (declare (K namify_module)) module_fragments
   212           |> fold (declare (namify_stmt o (fn Stmt stmt => stmt))) stmt_names;
   213         fun zip_fillup xs ys = xs ~~ ys @ replicate (length xs - length ys) NONE;
   214         fun select_names names = case filter (member (op =) stmt_names) names
   215          of [] => NONE
   216           | xs => SOME xs;
   217         val modify_stmts' = AList.make (snd o Graph.get_node nodes)
   218           #> split_list
   219           ##> map (fn Stmt stmt => stmt)
   220           #> (fn (names, stmts) => zip_fillup names (modify_stmts (names ~~ stmts)));
   221         val stmtss' = (maps modify_stmts' o map_filter select_names o Graph.strong_conn) nodes;
   222         val nodes'' = Graph.map (fn name => apsnd (fn Module content => Module (make_declarations nsps' content)
   223             | _ => case AList.lookup (op =) stmtss' name of SOME (SOME stmt) => Stmt stmt | _ => Dummy)) nodes';
   224         val data' = fold memorize_data stmt_names data;
   225       in (data', nodes'') end;
   226     val (_, hierarchical_program) = make_declarations empty_nsp proto_program;
   227 
   228     (* deresolving *)
   229     fun deresolver prefix_fragments name =
   230       let
   231         val (name_fragments, _) = dest_name name;
   232         val (_, (_, remainder)) = chop_prefix (op =) (prefix_fragments, name_fragments);
   233         val nodes = fold (fn name_fragment => fn nodes => case Graph.get_node nodes name_fragment
   234          of (_, Module (_, nodes)) => nodes) name_fragments hierarchical_program;
   235         val (base', _) = Graph.get_node nodes name;
   236       in Long_Name.implode (remainder @ [base']) end
   237         handle Graph.UNDEF _ => error ("Unknown statement name: " ^ labelled_name name);
   238 
   239   in { deresolver = deresolver, hierarchical_program = hierarchical_program } end;
   240 
   241 fun print_hierarchical { print_module, print_stmt, lift_markup } =
   242   let
   243     fun print_node _ (_, Dummy) =
   244           NONE
   245       | print_node prefix_fragments (name, Stmt stmt) =
   246           SOME (lift_markup (Code_Printer.markup_stmt name)
   247             (print_stmt prefix_fragments (name, stmt)))
   248       | print_node prefix_fragments (name_fragment, Module (data, nodes)) =
   249           let
   250             val prefix_fragments' = prefix_fragments @ [name_fragment]
   251           in
   252             Option.map (print_module prefix_fragments'
   253               name_fragment data) (print_nodes prefix_fragments' nodes)
   254           end
   255     and print_nodes prefix_fragments nodes =
   256       let
   257         val xs = (map_filter (fn name => print_node prefix_fragments
   258           (name, snd (Graph.get_node nodes name))) o rev o flat o Graph.strong_conn) nodes
   259       in if null xs then NONE else SOME xs end;
   260   in these o print_nodes [] end;
   261 
   262 end;