~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/stdlib/src/sofs.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
53
53
-export([fam2rel/1, rel2fam/1]).
54
54
 
55
55
-import(lists,
56
 
        [any/2, append/1, duplicate/2, flatten/1, foreach/2,
 
56
        [any/2, append/1, flatten/1, foreach/2,
57
57
         keysort/2, last/1, map/2, mapfoldl/3, member/2, merge/2,
58
58
         reverse/1, reverse/2, sort/1, umerge/1, umerge/2, usort/1]).
59
59
 
66
66
-compile({inline, 
67
67
          [{unify_types,2}, {match_types,2},
68
68
           {test_rel,3}, {symdiff,3}, 
69
 
           {subst,4}]}).
 
69
           {subst,3}]}).
70
70
 
71
71
-compile({inline, [{fam_binop,3}]}).
72
72
 
386
386
        false -> erlang:fault(type_mismatch, [S1, S2])
387
387
    end;
388
388
is_equal(S1, S2) when ?IS_ORDSET(S1), ?IS_ORDSET(S2) ->
389
 
    case match_types(?TYPE(S1), ?TYPE(S2)) of
 
389
    case match_types(?ORDTYPE(S1), ?ORDTYPE(S2)) of
390
390
        true  -> ?ORDDATA(S1) == ?ORDDATA(S2);
391
391
        false -> erlang:fault(type_mismatch, [S1, S2])
392
392
    end;
1266
1266
ordset_of_sets([S | Ss], L, T) when ?IS_SET(S) ->
1267
1267
    ordset_of_sets(Ss, [?LIST(S) | L], [[?TYPE(S)] | T]);
1268
1268
ordset_of_sets([S | Ss], L, T) when ?IS_ORDSET(S) ->
1269
 
    ordset_of_sets(Ss, [?LIST(S) | L], [?ORDTYPE(S) | T]);
 
1269
    ordset_of_sets(Ss, [?ORDDATA(S) | L], [?ORDTYPE(S) | T]);
1270
1270
ordset_of_sets([], L, T) ->
1271
1271
    ?ORDSET(list_to_tuple(reverse(L)), list_to_tuple(reverse(T)));
1272
1272
ordset_of_sets(_, _L, _T) ->
1273
1273
    error.
1274
1274
 
1275
1275
%% Inlined.
1276
 
rel(Ts, TS) ->
1277
 
    case {TS, is_type(TS)} of
1278
 
        {[Type], true} ->
1279
 
            case catch atoms_only(Type, 1) of
1280
 
                true when ?IS_RELATION(Type) ->
1281
 
                    rel(Ts, size(Type), Type);
1282
 
                _ ->
1283
 
                    rel_type(Ts, [], Type)
1284
 
            end;
1285
 
        _ ->
1286
 
            rel(Ts, TS, erlang:make_tuple(TS, ?ATOM_TYPE))
1287
 
    end.
1288
 
 
 
1276
rel(Ts, [Type]) ->
 
1277
    case is_type(Type) and atoms_only(Type, 1) of
 
1278
        true ->
 
1279
            rel(Ts, size(Type), Type);
 
1280
        false ->
 
1281
            rel_type(Ts, [], Type)
 
1282
    end;
 
1283
rel(Ts, Sz) ->
 
1284
    rel(Ts, Sz, erlang:make_tuple(Sz, ?ATOM_TYPE)).
 
1285
    
1289
1286
atoms_only(Type, I) when ?IS_ATOM_TYPE(?REL_TYPE(I, Type)) ->
1290
1287
    atoms_only(Type, I+1);
1291
 
atoms_only(Type, I) when I > size(Type) ->
1292
 
    true.
 
1288
atoms_only(Type, I) when I > size(Type), ?IS_RELATION(Type) ->
 
1289
    true;
 
1290
atoms_only(_Type, _I) ->
 
1291
    false.
1293
1292
 
1294
1293
rel(Ts, Sz, Type) when Sz >= 1 ->
1295
1294
    SL = usort(Ts),
2355
2354
                NT -> {?LIST(NS), NT}
2356
2355
            end;
2357
2356
        NS when ?IS_ORDSET(NS) ->
2358
 
            case unify_types(NType, NT = ?TYPE(NS)) of
 
2357
            case unify_types(NType, NT = ?ORDTYPE(NS)) of
2359
2358
                [] -> type_mismatch;
2360
 
                NT -> {?LIST(NS), NT}
 
2359
                NT -> {?ORDDATA(NS), NT}
2361
2360
            end;
2362
2361
        _ ->
2363
2362
            badarg