~rdoering/ubuntu/intrepid/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Soren Hansen
  • Date: 2007-05-01 16:57:10 UTC
  • mfrom: (1.1.9 upstream)
  • Revision ID: james.westby@ubuntu.com-20070501165710-2sapk0hp2gf3o0ip
Tags: 1:11.b.4-2ubuntu1
* Merge with Debian Unstable. Remaining changes:
  - Add -fno-stack-protector to fix broken crypto_drv.
* DebianMaintainerField update.

Show diffs side-by-side

added added

removed removed

Lines of Context:
253
253
format_error({used_generator_variable, V}) ->
254
254
    io_lib:format("generated variable ~w must not be used in list expression",
255
255
                  [V]);
 
256
format_error(binary_generator) ->
 
257
    io_lib:format("cannot handle binary generators", []);
256
258
format_error(too_complex_join) ->
257
259
    io_lib:format("cannot handle join of three or more generators efficiently",
258
260
                  []);
272
274
format_error({premature_eof, FileName}) ->
273
275
    io_lib:format("\"~s\": end-of-file was encountered inside some binary term", 
274
276
                  [FileName]);
275
 
format_error({not_a_directory, FileName}) ->
276
 
    io_lib:format("\"~s\": the file supplied with the tmpdir option "
277
 
                  "is not a directory", [FileName]);
278
277
format_error({error, Module, Reason}) ->
279
278
    Module:format_error(Reason);
280
279
format_error(E) ->
290
289
        {B1, B2} when B1 =:= badarg; B2 =:= badarg ->
291
290
            erlang:error(badarg, [QH, Options]);
292
291
        {[GUnique, GCache, Flat, Format, NElements, TmpDir, MaxList], H} ->
293
 
            Prep = prepare_qlc(H, [], GUnique, GCache, TmpDir, MaxList),
294
 
            Info = le_info(Prep),
295
 
            AbstractCode = abstract(Info, Flat, NElements),
296
 
            case Format of
297
 
                abstract_code ->
298
 
                    AbstractCode;
299
 
                string ->
300
 
                    lists:flatten(erl_pp:expr(AbstractCode, 0, none));
301
 
                debug -> % Not documented. Intended for testing only.
302
 
                    Info
 
292
            try
 
293
                Prep = prepare_qlc(H, [], GUnique, GCache, TmpDir, MaxList),
 
294
                Info = le_info(Prep),
 
295
                AbstractCode = abstract(Info, Flat, NElements),
 
296
                case Format of
 
297
                    abstract_code ->
 
298
                        AbstractCode;
 
299
                    string ->
 
300
                        lists:flatten(erl_pp:expr(AbstractCode, 0, none));
 
301
                    debug -> % Not documented. Intended for testing only.
 
302
                        Info
 
303
                end
 
304
            catch Term ->
 
305
                case erlang:get_stacktrace() of
 
306
                    [?THROWN_ERROR | _] ->
 
307
                        Term;
 
308
                    Stacktrace ->
 
309
                        erlang:raise(throw, Term, Stacktrace)
 
310
                end
303
311
            end
304
312
    end.
305
313
 
1322
1330
                          MS
1323
1331
                  end,
1324
1332
            Prep = Prep0#prepared{qh = LE0#qlc_table{lu_vals = LuV,ms = MS1}},
1325
 
            {replace, Fs, LU, may_create_simple(Opt, Prep)};
 
1333
            {replace, Fs, LU, Prep};
1326
1334
        #qlc_table{} when LU ->
1327
1335
            Prep = Prep0#prepared{qh = LE0#qlc_table{lu_vals = LuV}},
1328
 
            {skip, SkipFils, LU, may_create_simple(Opt, Prep)};
 
1336
            {skip, SkipFils, LU, Prep};
1329
1337
        #qlc_table{trav_MS = true} when MS =/= no_match_spec ->
1330
1338
            Prep = Prep0#prepared{qh = LE0#qlc_table{ms = MS}},
1331
1339
            {replace, Fs, false, may_create_simple(Opt, Prep)};
1463
1471
 
1464
1472
sort_unique(true, #qlc_sort{opts = SortOptions, keypos = sort}=Sort) ->
1465
1473
    Sort#qlc_sort{unique = false, 
1466
 
                  opts = lists:keydelete(unique, 1, SortOptions)};
 
1474
                  opts = lists:keydelete(unique, 
 
1475
                                         1, 
 
1476
                                         lists:delete(unique, SortOptions))};
1467
1477
sort_unique(_, Sort) ->
1468
1478
    Sort.
1469
1479
 
1748
1758
            TmpDir = Opt#qlc_opt.tmpdir,
1749
1759
            Opts = [{tmpdir,Dir} || Dir <- [TmpDir], Dir =/= ""],
1750
1760
            Sort = #qlc_sort{h = LE, keypos = {keysort, Col}, unique = false,
1751
 
                             compressed = false, order = ascending,
 
1761
                             compressed = [], order = ascending,
1752
1762
                             opts = Opts, tmpdir = TmpDir},
1753
1763
            #prepared{qh = Sort, sorted = no, join = no};
1754
1764
        false ->
2025
2035
    _ = call(PreFun, PreFunArgs, ok, Post),
2026
2036
    case LuVals of
2027
2037
        {Pos, Vals} when MS =:= no_match_spec ->
2028
 
            fun() -> LuF(Pos, Vals) end;
 
2038
            LuF(Pos, Vals);
2029
2039
        {Pos, Vals} ->
2030
 
            fun() ->
2031
 
                    case LuF(Pos, Vals) of
2032
 
                        [] -> 
2033
 
                            [];
2034
 
                        Objs when is_list(Objs) -> 
2035
 
                            ets:match_spec_run(Objs, 
2036
 
                                               ets:match_spec_compile(MS));
2037
 
                        Error ->
2038
 
                            Error
2039
 
                    end
 
2040
            case LuF(Pos, Vals) of
 
2041
                [] -> 
 
2042
                    [];
 
2043
                Objs when is_list(Objs) -> 
 
2044
                    ets:match_spec_run(Objs, 
 
2045
                                       ets:match_spec_compile(MS));
 
2046
                Error ->
 
2047
                    throw_error(Error)
2040
2048
            end;
2041
2049
        _ when not TravMS ->
2042
2050
            TraverseFun;
2466
2474
            L
2467
2475
    end.
2468
2476
    
2469
 
lcache1([]=Cont, {Key, PostL, _TmpDir, _MaxList}, _Sz, Ack) ->
 
2477
lcache1([]=Cont, {Key, PostL, _TmpDir, _MaxList}, _Sz, Acc) ->
2470
2478
    local_post(PostL),
2471
2479
    case get(Key) of
2472
2480
        undefined -> 
2473
 
            put(Key, lists:reverse(Ack));
 
2481
            put(Key, lists:reverse(Acc));
2474
2482
        {file, Fd, TmpFile, _F} ->
2475
 
            lcache_write(Fd, TmpFile, Ack)
 
2483
            lcache_write(Fd, TmpFile, Acc)
2476
2484
    end,
2477
2485
    Cont;
2478
 
lcache1(H, State, Sz, Ack) when Sz < 0 ->
 
2486
lcache1(H, State, Sz, Acc) when Sz < 0 ->
2479
2487
    {Key, PostL, TmpDir, MaxList} = State,
2480
2488
    {FileName, Fd} = 
2481
2489
        case get(Key) of
2487
2495
                put(Key, {file, Fd0, FName, F}),
2488
2496
                {FName, Fd0}
2489
2497
        end,
2490
 
    lcache_write(Fd, FileName, Ack),
 
2498
    lcache_write(Fd, FileName, Acc),
2491
2499
    lcache1(H, State, MaxList, []);
2492
 
lcache1([Object | Cont], State, Sz0, Ack) ->
 
2500
lcache1([Object | Cont], State, Sz0, Acc) ->
2493
2501
    Sz = decr_list_size(Sz0, Object),
2494
 
    [Object | fun() -> lcache1(Cont, State, Sz, [Object | Ack]) end];
2495
 
lcache1(F, State, Sz, Ack) when is_function(F) ->
2496
 
    lcache1(F(), State, Sz, Ack);
2497
 
lcache1(Term, _State, _Sz, _Ack) ->
 
2502
    [Object | fun() -> lcache1(Cont, State, Sz, [Object | Acc]) end];
 
2503
lcache1(F, State, Sz, Acc) when is_function(F) ->
 
2504
    lcache1(F(), State, Sz, Acc);
 
2505
lcache1(Term, _State, _Sz, _Acc) ->
2498
2506
    throw_error(Term).
2499
2507
    
2500
2508
lcache_write(Fd, FileName, L) ->