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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2004-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2004-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(qlc).
528
528
                  false ->
529
529
                      Options0
530
530
              end,
531
 
    V = case lists:keysearch(Key, 1, Options) of
532
 
            {value, {format_fun, U=undefined}} ->
533
 
                {ok, U};
534
 
            {value, {info_fun, U=undefined}} ->
535
 
                {ok, U};
536
 
            {value, {lookup_fun, U=undefined}} ->
537
 
                {ok, U};
538
 
            {value, {parent_fun, U=undefined}} ->
539
 
                {ok, U};
540
 
            {value, {post_fun, U=undefined}} ->
541
 
                {ok, U};
542
 
            {value, {pre_fun, U=undefined}} ->
543
 
                {ok, U};
544
 
            {value, {info_fun, Fun}} when is_function(Fun), 
545
 
                                          is_function(Fun, 1) ->
546
 
                {ok, Fun};
547
 
            {value, {pre_fun, Fun}} when is_function(Fun),
548
 
                                         is_function(Fun, 1) ->
549
 
                {ok, Fun};
550
 
            {value, {post_fun, Fun}} when is_function(Fun), 
551
 
                                          is_function(Fun, 0) ->
552
 
                {ok, Fun};
553
 
            {value, {lookup_fun, Fun}} when is_function(Fun),
554
 
                                            is_function(Fun, 2) ->
555
 
                {ok, Fun};
556
 
            {value, {max_lookup, Max}} when is_integer(Max), Max >= 0 ->
 
531
    V = case lists:keyfind(Key, 1, Options) of
 
532
            {format_fun, U=undefined} ->
 
533
                {ok, U};
 
534
            {info_fun, U=undefined} ->
 
535
                {ok, U};
 
536
            {lookup_fun, U=undefined} ->
 
537
                {ok, U};
 
538
            {parent_fun, U=undefined} ->
 
539
                {ok, U};
 
540
            {post_fun, U=undefined} ->
 
541
                {ok, U};
 
542
            {pre_fun, U=undefined} ->
 
543
                {ok, U};
 
544
            {info_fun, Fun} when is_function(Fun), is_function(Fun, 1) ->
 
545
                {ok, Fun};
 
546
            {pre_fun, Fun} when is_function(Fun), is_function(Fun, 1) ->
 
547
                {ok, Fun};
 
548
            {post_fun, Fun} when is_function(Fun), is_function(Fun, 0) ->
 
549
                {ok, Fun};
 
550
            {lookup_fun, Fun} when is_function(Fun), is_function(Fun, 2) ->
 
551
                {ok, Fun};
 
552
            {max_lookup, Max} when is_integer(Max), Max >= 0 ->
557
553
                {ok, Max};
558
 
            {value, {max_lookup, infinity}} ->
 
554
            {max_lookup, infinity} ->
559
555
                {ok, -1};
560
 
            {value, {format_fun, Fun}} when is_function(Fun),
561
 
                                            is_function(Fun, 1) ->
562
 
                {ok, Fun};
563
 
            {value, {parent_fun, Fun}} when is_function(Fun),
564
 
                                            is_function(Fun, 0) ->
565
 
                {ok, Fun};
566
 
            {value, {key_equality, KE='=='}}->
567
 
                {ok, KE};
568
 
            {value, {key_equality, KE='=:='}}->
569
 
                {ok, KE};
570
 
            {value, {join, J=any}} ->
571
 
                {ok, J};
572
 
            {value, {join, J=nested_loop}} ->
573
 
                {ok, J};
574
 
            {value, {join, J=merge}} ->
575
 
                {ok, J};
576
 
            {value, {join, J=lookup}} ->
577
 
                {ok, J};
578
 
            {value, {lookup, LookUp}} when LookUp; 
579
 
                                           not LookUp; 
580
 
                                           LookUp =:= any ->
 
556
            {format_fun, Fun} when is_function(Fun), is_function(Fun, 1) ->
 
557
                {ok, Fun};
 
558
            {parent_fun, Fun} when is_function(Fun), is_function(Fun, 0) ->
 
559
                {ok, Fun};
 
560
            {key_equality, KE='=='} ->
 
561
                {ok, KE};
 
562
            {key_equality, KE='=:='} ->
 
563
                {ok, KE};
 
564
            {join, J=any} ->
 
565
                {ok, J};
 
566
            {join, J=nested_loop} ->
 
567
                {ok, J};
 
568
            {join, J=merge} ->
 
569
                {ok, J};
 
570
            {join, J=lookup} ->
 
571
                {ok, J};
 
572
            {lookup, LookUp} when is_boolean(LookUp); LookUp =:= any ->
581
573
                {ok, LookUp};
582
 
            {value, {max_list_size, Max}} when is_integer(Max), Max >= 0 ->
 
574
            {max_list_size, Max} when is_integer(Max), Max >= 0 ->
583
575
                {ok, Max};
584
 
            {value, {tmpdir_usage, TmpUsage}} when TmpUsage =:= allowed;
585
 
                                                   TmpUsage =:= not_allowed;
586
 
                                                   TmpUsage =:= info_msg;
587
 
                                                   TmpUsage =:= warning_msg;
588
 
                                                   TmpUsage =:= error_msg ->
 
576
            {tmpdir_usage, TmpUsage} when TmpUsage =:= allowed;
 
577
                                          TmpUsage =:= not_allowed;
 
578
                                          TmpUsage =:= info_msg;
 
579
                                          TmpUsage =:= warning_msg;
 
580
                                          TmpUsage =:= error_msg ->
589
581
                {ok, TmpUsage};
590
 
            {value, {unique, Unique}} when Unique; not Unique ->
 
582
            {unique, Unique} when is_boolean(Unique) ->
591
583
                {ok, Unique};
592
 
            {value, {cache, Cache}} when Cache; not Cache; Cache =:= list ->
 
584
            {cache, Cache} when is_boolean(Cache); Cache =:= list ->
593
585
                {ok, Cache};
594
 
            {value, {cache, ets}} ->
 
586
            {cache, ets} ->
595
587
                {ok, true};
596
 
            {value, {cache, no}} ->
 
588
            {cache, no} ->
597
589
                {ok, false};
598
 
            {value, {unique_all, UniqueAll}} when UniqueAll; not UniqueAll ->
 
590
            {unique_all, UniqueAll} when is_boolean(UniqueAll) ->
599
591
                {ok, UniqueAll};
600
 
            {value, {cache_all, CacheAll}} when CacheAll; 
601
 
                                                not CacheAll;
602
 
                                                CacheAll =:= list ->
 
592
            {cache_all, CacheAll} when is_boolean(CacheAll);
 
593
                                       CacheAll =:= list ->
603
594
                {ok, CacheAll};
604
 
            {value, {cache_all, ets}} ->
 
595
            {cache_all, ets} ->
605
596
                {ok, true};
606
 
            {value, {cache_all, no}} ->
 
597
            {cache_all, no} ->
607
598
                {ok, false};
608
 
            {value, {spawn_options, default}} ->
 
599
            {spawn_options, default} ->
609
600
                {ok, default};
610
 
            {value, {spawn_options, SpawnOptions}} ->
 
601
            {spawn_options, SpawnOptions} ->
611
602
                case is_proper_list(SpawnOptions) of
612
603
                    true -> 
613
604
                        {ok, SpawnOptions};
614
605
                    false ->
615
606
                        badarg
616
607
                end;
617
 
            {value, {flat, Flat}} when Flat; not Flat ->
 
608
            {flat, Flat} when is_boolean(Flat) ->
618
609
                {ok, Flat};
619
 
            {value, {format, Format}} when Format =:= string;
620
 
                                           Format =:= abstract_code;
621
 
                                           Format =:= debug ->
 
610
            {format, Format} when Format =:= string;
 
611
                                  Format =:= abstract_code;
 
612
                                  Format =:= debug ->
622
613
                {ok, Format};
623
 
            {value, {n_elements, NElements}} when NElements =:= infinity;
624
 
                                                  is_integer(NElements),
625
 
                                                   NElements > 0 ->
 
614
            {n_elements, NElements} when NElements =:= infinity;
 
615
                                         is_integer(NElements),
 
616
                                         NElements > 0 ->
626
617
                {ok, NElements};
627
 
            {value, {depth, Depth}} when Depth =:= infinity;
628
 
                                         is_integer(Depth), Depth >= 0 ->
 
618
            {depth, Depth} when Depth =:= infinity;
 
619
                                is_integer(Depth), Depth >= 0 ->
629
620
                {ok, Depth};
630
 
            {value, {order, Order}} when is_function(Order), 
631
 
                                           is_function(Order, 2);
632
 
                                         (Order =:= ascending);
633
 
                                         (Order =:= descending) ->
 
621
            {order, Order} when is_function(Order), is_function(Order, 2);
 
622
                                (Order =:= ascending);
 
623
                                (Order =:= descending) ->
634
624
                {ok, Order};
635
 
            {value, {compressed, Comp}} when Comp ->
 
625
            {compressed, Comp} when Comp ->
636
626
                {ok, [compressed]};
637
 
            {value, {compressed, Comp}} when not Comp ->
 
627
            {compressed, Comp} when not Comp ->
638
628
                {ok, []};
639
 
            {value, {tmpdir, T}} ->
 
629
            {tmpdir, T} ->
640
630
                {ok, T};
641
 
            {value, {size, Size}} when is_integer(Size), Size > 0 ->
 
631
            {size, Size} when is_integer(Size), Size > 0 ->
642
632
                {ok, Size};
643
 
            {value, {no_files, NoFiles}} when is_integer(NoFiles), 
644
 
                                              NoFiles > 1 ->
 
633
            {no_files, NoFiles} when is_integer(NoFiles), NoFiles > 1 ->
645
634
                {ok, NoFiles};
646
 
            {value, {Key, _}} ->
 
635
            {Key, _} ->
647
636
                badarg;
648
637
            false ->
649
638
                Default = default_option(Key),
1457
1446
                {?qual_data(QNum, GoI, SI, {gen, Prep}), ModGens}
1458
1447
        end,
1459
1448
    {Qdata, ModGens} = lists:mapfoldl(F, [], Qdata0),
1460
 
    SomeLookUp = lists:keymember(true, 2, ModGens) =/= false,
 
1449
    SomeLookUp = lists:keymember(true, 2, ModGens),
1461
1450
    check_lookup_option(Opt, SomeLookUp),
1462
1451
    case ModGens of
1463
1452
        [{_QNum, _LookUp, all, OnePrep}] ->
1503
1492
 
1504
1493
prep_gen(#qlc_table{lu_vals = LuV0, ms = MS0, trav_MS = TravMS,
1505
1494
                    info_fun = IF, lookup_fun = LU_fun,
1506
 
                    key_equality = KeyEquality}=LE0, 
 
1495
                    key_equality = KeyEquality}=LE0,
1507
1496
         Prep0, PosFun0, {MS, Fs}, Opt) ->
1508
1497
    PosFun = PosFun0(KeyEquality),
1509
1498
    {LuV, {STag,SkipFils}} = find_const_positions(IF, LU_fun, PosFun, Opt),
1998
1987
    Optz#optz{cache = false}.
1999
1988
 
2000
1989
maybe_sort(LE, QNum, DoSort, Opt) ->
2001
 
    case lists:keysearch(QNum, 1, DoSort) of
2002
 
        {value, {QNum, Col}} ->
 
1990
    case lists:keyfind(QNum, 1, DoSort) of
 
1991
        {QNum, Col} ->
2003
1992
            #qlc_opt{tmpdir = TmpDir, tmpdir_usage = TmpUsage} = Opt,
2004
1993
            SortOpts = [{tmpdir,Dir} || Dir <- [TmpDir], Dir =/= ""],
2005
1994
            Sort = #qlc_sort{h = LE, keypos = {keysort, Col}, unique = false,
2025
2014
%% specification it must be applied _after_ the lookup join (the
2026
2015
%% filter must not be skipped!).
2027
2016
activate_join_lookup_filter(QNum, Qdata) ->
2028
 
    {value, {_,GoI2,SI2,{gen,Prep2}}} = lists:keysearch(QNum, 1, Qdata),
 
2017
    {_,GoI2,SI2,{gen,Prep2}} = lists:keyfind(QNum, 1, Qdata),
2029
2018
    Table2 = Prep2#prepared.qh,
2030
2019
    NPrep2 = Prep2#prepared{qh = Table2#qlc_table{ms = no_match_spec}},
2031
2020
    %% Table2#qlc_table.ms has been reset; the filter will be run.
2059
2048
 
2060
2049
opt_join_lu([{{_Q1,_C1,Q2,_C2}=J,[{lookup_join,_KEols,JKE,Skip0} | _]} | LJ], 
2061
2050
            Qdata, LU_SkipQuals) ->
2062
 
    {value, {Q2,_,_,{gen,Prep2}}} = lists:keysearch(Q2, 1, Qdata),
 
2051
    {Q2,_,_,{gen,Prep2}} = lists:keyfind(Q2, 1, Qdata),
2063
2052
    #qlc_table{ms = MS, key_equality = KE, 
2064
2053
               lookup_fun = LU_fun} = Prep2#prepared.qh,
2065
2054
    %% If there is no filter to skip (the match spec was derived 
2670
2659
%% Don't use the file_sorter unless it is known that objects will be
2671
2660
%% put on a temporary file (optimization).
2672
2661
sort_handle(H, ListFun, FileFun, SortOptions, Post, LocalPost, TmpUsageM) ->
2673
 
    Size = case lists:keysearch(size, 1, SortOptions) of
2674
 
               {value, {size, Size0}} -> Size0;
 
2662
    Size = case lists:keyfind(size, 1, SortOptions) of
 
2663
               {size, Size0} -> Size0;
2675
2664
               false -> default_option(size)
2676
2665
           end,
2677
2666
    sort_cache(H, [], Size, {ListFun, FileFun, Post, LocalPost, TmpUsageM}).
2891
2880
            Object = case ets:lookup(UTab, Hash) of
2892
2881
                         [{Hash, SeqNo, Object0}] -> Object0;
2893
2882
                         HashSeqObjects -> 
2894
 
                             {value, {Hash, SeqNo, Object0}} = 
2895
 
                                 lists:keysearch(SeqNo, 2, HashSeqObjects),
 
2883
                             {Hash, SeqNo, Object0} =
 
2884
                                 lists:keyfind(SeqNo, 2, HashSeqObjects),
2896
2885
                             Object0
2897
2886
                     end,
2898
2887
            [Object | fun() -> ucache_recall(UTab, MTab, SeqNo + 1) end]
3403
3392
 
3404
3393
tmp_merge_file(MergeId) ->
3405
3394
    TmpFiles = get(?MERGE_JOIN_FILE),
3406
 
    case lists:keysearch(MergeId, 1, TmpFiles) of
3407
 
        {value, {MergeId, Fd, FileName}} ->
 
3395
    case lists:keyfind(MergeId, 1, TmpFiles) of
 
3396
        {MergeId, Fd, FileName} ->
3408
3397
            {Fd, FileName};
3409
3398
        false ->
3410
3399
            none