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

« back to all changes in this revision

Viewing changes to lib/tv/src/tv_pg_gridfcns.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:
75
75
    #process_variables{parent_pid  = ParentPid,
76
76
                       grid_params = GridP}   = ProcVars,
77
77
    
78
 
    #grid_params{bg_color        = GridBgColor,
79
 
                 fg_color        = GridFgColor,
 
78
    #grid_params{fg_color        = GridFgColor,
80
79
                 nof_cols        = NofCols,
81
80
                 col_width       = DefaultColWidth,
82
81
                 first_col_shown = FirstColShown,
166
165
    
167
166
    #grid_params{bg_frame         = BgFrame,
168
167
                 fg_frame         = FgFrame,
169
 
                 grid_xpos        = GridXpos,
170
 
                 grid_ypos        = GridYpos,            
171
168
                 nof_cols         = NofCols,
172
169
                 nof_rows         = NofRows,
173
170
                 col_width        = DefaultColWidth,
174
 
                 max_col_width    = MaxColWidth,
175
 
                 min_col_width    = MinColWidth,
176
171
                 first_col_shown  = FirstColShown,
177
172
                 col_widths       = ColWidths,
178
173
                 row_height       = RowHeight,
376
371
                 nof_rows         = NofRows,
377
372
                 nof_rows_shown   = NofRowsShown,
378
373
                 row_ids          = RowIds,
379
 
                 col_ids          = ColIds,
380
374
                 lists_as_strings = ListAsStr}  = GridP,
381
375
    
382
376
    NofColsShown = length(ColsShown),
418
412
                       mark_params = MarkP}   = ProcVars,
419
413
    
420
414
    #grid_params{grid_width       = Width,
421
 
                 grid_height      = Height,
422
415
                 nof_cols         = NofCols,
423
416
                 nof_rows         = NofRows,
424
417
                 nof_rows_shown   = NofRowsShown,
672
665
    case {VirtualCol, VirtualRow} of
673
666
        {undefined, undefined} ->
674
667
            update_marked_cells(CellId, CellId, false);
675
 
        {AnyCol, undefined} ->
 
668
        {_AnyCol, undefined} ->
676
669
            NofColsShown = length(ColsShown),
677
670
            unmark_col(VirtualCol, FirstColShown, FirstColShown + NofColsShown - 1, 
678
671
                       ColIds);
679
 
        {undefined, AnyRow} ->
 
672
        {undefined, _AnyRow} ->
680
673
            unmark_row(VirtualRow, FirstRowShown, FirstRowShown + NofRowsShown - 1, 
681
674
                       RowIds);
682
675
        _Other ->
725
718
                 col_ids         = ColIds,
726
719
                 row_ids         = RowIds}  = GridP,
727
720
 
728
 
    #mark_params{cell_id     = CellId,
729
 
                 virtual_col = VirtualCol,
 
721
    #mark_params{virtual_col = VirtualCol,
730
722
                 virtual_row = VirtualRow} = MarkP,
731
723
 
732
724
 
733
 
    NewMarkP = case {VirtualCol, VirtualRow} of
734
 
                   {undefined, undefined} ->
735
 
                       NofColsShown = length(ColsShown),
736
 
                       move_marked_cell(FirstCol, FirstRow, NofColsShown, 
737
 
                                        NofRowsShown, RowIds, MarkP);
738
 
                   {AnyCol, undefined} ->
739
 
                       NofColsShown = length(ColsShown),
740
 
                       OldLastCol = OldFirstCol + NofColsShown - 1,
741
 
                       LastCol    = FirstCol + NofColsShown - 1,
742
 
                       move_marked_col(VirtualCol, OldFirstCol, OldLastCol, 
743
 
                                       FirstCol, LastCol, ColIds, MarkP);
744
 
                   {undefined, AnyRow} ->
745
 
                       OldLastRow = OldFirstRow + NofRowsShown - 1,
746
 
                       LastRow    = FirstRow + NofRowsShown - 1,
747
 
                       move_marked_row(VirtualRow, OldFirstRow, OldLastRow, 
748
 
                                       FirstRow, LastRow, RowIds, MarkP);
749
 
                   {CellCol, CellRow} ->
750
 
                       NofColsShown = length(ColsShown),
751
 
                       move_marked_cell(FirstCol, FirstRow, NofColsShown, 
752
 
                                        NofRowsShown, RowIds, MarkP)
753
 
               end.
 
725
    case {VirtualCol, VirtualRow} of
 
726
        {undefined, undefined} ->
 
727
            NofColsShown = length(ColsShown),
 
728
            move_marked_cell(FirstCol, FirstRow, NofColsShown, 
 
729
                             NofRowsShown, RowIds, MarkP);
 
730
        {_AnyCol, undefined} ->
 
731
            NofColsShown = length(ColsShown),
 
732
            OldLastCol = OldFirstCol + NofColsShown - 1,
 
733
            LastCol    = FirstCol + NofColsShown - 1,
 
734
            move_marked_col(VirtualCol, OldFirstCol, OldLastCol, 
 
735
                            FirstCol, LastCol, ColIds, MarkP);
 
736
        {undefined, _AnyRow} ->
 
737
            OldLastRow = OldFirstRow + NofRowsShown - 1,
 
738
            LastRow    = FirstRow + NofRowsShown - 1,
 
739
            move_marked_row(VirtualRow, OldFirstRow, OldLastRow, 
 
740
                            FirstRow, LastRow, RowIds, MarkP);
 
741
        {_CellCol, _CellRow} ->
 
742
            NofColsShown = length(ColsShown),
 
743
            move_marked_cell(FirstCol, FirstRow, NofColsShown, 
 
744
                             NofRowsShown, RowIds, MarkP)
 
745
    end.
754
746
    
755
747
 
756
748
 
779
771
                 col_ids         = ColIds,
780
772
                 row_ids         = RowIds}  = GridP,
781
773
 
782
 
    #mark_params{cell_id     = CellId,
783
 
                 virtual_col = VirtualCol,
 
774
    #mark_params{virtual_col = VirtualCol,
784
775
                 virtual_row = VirtualRow} = MarkP,
785
776
 
786
777
 
789
780
            NofColsShown = length(ColsShown),
790
781
            move_marked_cell(FirstCol, FirstRow, NofColsShown, NofRowsShown, 
791
782
                             RowIds, MarkP);
792
 
        {AnyCol, undefined} ->
 
783
        {_AnyCol, undefined} ->
793
784
            NofColsShown = length(ColsShown),
794
785
            LastCol    = FirstCol + NofColsShown - 1,
795
786
            mark_col(VirtualCol, FirstCol, LastCol, ColIds, ?GRID_MARK_COLOR);
796
 
        {undefined, AnyRow} ->
 
787
        {undefined, _AnyRow} ->
797
788
            LastRow    = FirstRow + NofRowsShown - 1,
798
789
            mark_row(VirtualRow, FirstRow, LastRow, RowIds, ?GRID_MARK_COLOR);
799
 
        {CellCol, CellRow} ->
 
790
        {_CellCol, _CellRow} ->
800
791
            NofColsShown = length(ColsShown),
801
792
            move_marked_cell(FirstCol, FirstRow, NofColsShown, NofRowsShown, 
802
793
                             RowIds, MarkP)
844
835
%%======================================================================
845
836
 
846
837
 
847
 
mark_col(VirtualCol, FirstCol, LastCol, ColIds, Color) when VirtualCol < FirstCol ->
848
 
    done;
849
 
mark_col(VirtualCol, FirstCol, LastCol, ColIds, Color) when VirtualCol > LastCol ->
850
 
    done;
851
 
mark_col(VirtualCol, FirstCol, LastCol, ColIds, Color) ->
 
838
mark_col(VirtualCol, FirstCol, _LastCol, _ColIds, _Color) when VirtualCol < FirstCol ->
 
839
    done;
 
840
mark_col(VirtualCol, _FirstCol, LastCol, _ColIds, _Color) when VirtualCol > LastCol ->
 
841
    done;
 
842
mark_col(VirtualCol, FirstCol, _LastCol, ColIds, Color) ->
852
843
    RealCol = VirtualCol - FirstCol + 1,
853
844
    MarkedColIds = lists:nth(RealCol, ColIds),
854
845
    mark_all_cells(MarkedColIds, Color).
892
883
%%======================================================================
893
884
 
894
885
 
895
 
mark_all_cells([], Color) ->
 
886
mark_all_cells([], _Color) ->
896
887
    done;
897
888
mark_all_cells([CellId | T], Color) ->
898
889
    gs:config(CellId, [{bg, Color}]),
916
907
%%======================================================================
917
908
 
918
909
 
919
 
mark_row(VirtualRow, FirstRow, LastRow, RowIds, Color) when VirtualRow < FirstRow ->
920
 
    done;
921
 
mark_row(VirtualRow, FirstRow, LastRow, RowIds, Color) when VirtualRow > LastRow ->
922
 
    done;
923
 
mark_row(VirtualRow, FirstRow, LastRow, RowIds, Color) ->
 
910
mark_row(VirtualRow, FirstRow, _LastRow, _RowIds, _Color) when VirtualRow < FirstRow ->
 
911
    done;
 
912
mark_row(VirtualRow, _FirstRow, LastRow, _RowIds, _Color) when VirtualRow > LastRow ->
 
913
    done;
 
914
mark_row(VirtualRow, FirstRow, _LastRow, RowIds, Color) ->
924
915
    RealRow      = VirtualRow - FirstRow + 1,
925
916
    MarkedRowIds = lists:nth(RealRow, RowIds),
926
917
    mark_all_cells(MarkedRowIds, Color).
1036
1027
%%======================================================================
1037
1028
 
1038
1029
 
1039
 
check_if_new_mark_visible(Col, Row, NofCols, NofRows) when Col > NofCols ->
1040
 
    false;
1041
 
check_if_new_mark_visible(Col, Row, NofCols, NofRows) when Col =< 0 ->
1042
 
    false;
1043
 
check_if_new_mark_visible(Col, Row, NofCols, NofRows) when Row > NofRows ->
1044
 
    false;
1045
 
check_if_new_mark_visible(Col, Row, NofCols, NofRows) when Row =< 0 ->
1046
 
    false;
1047
 
check_if_new_mark_visible(Col, Row, NofCols, NofRows) ->
 
1030
check_if_new_mark_visible(Col, _Row, NofCols, _NofRows) when Col > NofCols ->
 
1031
    false;
 
1032
check_if_new_mark_visible(Col, _Row, _NofCols, _NofRows) when Col =< 0 ->
 
1033
    false;
 
1034
check_if_new_mark_visible(_Col, Row, _NofCols, NofRows) when Row > NofRows ->
 
1035
    false;
 
1036
check_if_new_mark_visible(_Col, Row, _NofCols, _NofRows) when Row =< 0 ->
 
1037
    false;
 
1038
check_if_new_mark_visible(_Col, _Row, _NofCols, _NofRows) ->
1048
1039
    true.
1049
1040
    
1050
1041
 
1068
1059
%%======================================================================
1069
1060
 
1070
1061
 
1071
 
update_marked_cells(CellId, OldCellId, MarkedCell) when CellId == OldCellId ->
 
1062
update_marked_cells(CellId, OldCellId, _MarkedCell) when CellId == OldCellId ->
1072
1063
    gs:config(CellId, [{bg, ?DEFAULT_GRID_BGCOLOR}]);
1073
 
update_marked_cells(CellId, undefined, false) ->
 
1064
update_marked_cells(_CellId, undefined, false) ->
1074
1065
    done;
1075
1066
update_marked_cells(CellId, undefined, true) ->
1076
1067
    gs:config(CellId, [{bg, ?GRID_MARK_COLOR}]);
1077
1068
update_marked_cells(CellId, OldCellId, true) ->
1078
1069
    gs:config(OldCellId, [{bg, ?DEFAULT_GRID_BGCOLOR}]),
1079
1070
    gs:config(CellId, [{bg, ?GRID_MARK_COLOR}]);
1080
 
update_marked_cells(CellId, OldCellId, false) ->
 
1071
update_marked_cells(_CellId, OldCellId, false) ->
1081
1072
    gs:config(OldCellId, [{bg, ?DEFAULT_GRID_BGCOLOR}]).
1082
1073
 
1083
1074
    
1137
1128
 
1138
1129
refresh_visible_rows([], _FirstColShown, _NofColsShown, _DataList, _ListAsStr) ->
1139
1130
    done;
1140
 
refresh_visible_rows(RowIds, FirstColShown, NofColsShown, [], ListAsStr) ->
 
1131
refresh_visible_rows(RowIds, _FirstColShown, _NofColsShown, [], _ListAsStr) ->
1141
1132
    clear_cols_or_rows(RowIds);
1142
1133
refresh_visible_rows([OneRowIds | RemRowIds], FirstColShown, NofColsShown,
1143
1134
                    [DataItemList | RemDataItemLists], ListAsStr) ->
1166
1157
 
1167
1158
update_visible_rows([], _FirstColShown, _NofColsShown, _DataList, _ListAsStr) ->
1168
1159
    done;
1169
 
update_visible_rows(RowIds, FirstColShown, NofColsShown, [], _ListAsStr) ->
 
1160
update_visible_rows(RowIds, _FirstColShown, _NofColsShown, [], _ListAsStr) ->
1170
1161
    clear_cols_or_rows(RowIds);
1171
1162
update_visible_rows([OneRowIds | RemRowIds], FirstColShown, NofColsShown,
1172
1163
                    [DataItem | RemData], ListAsStr) ->
1244
1235
make_row_data_list(N, NofRows, []) ->
1245
1236
       % If NofRows == N, we get the empty list here!
1246
1237
    lists:duplicate(NofRows- N, notext);
1247
 
make_row_data_list(N, NofRows, [DataItem | RemData]) when N > NofRows ->
 
1238
make_row_data_list(N, NofRows, [_DataItem | _RemData]) when N > NofRows ->
1248
1239
    [];
1249
1240
make_row_data_list(N, NofRows, [DataItem | RemData]) ->
1250
1241
       % We convert the received item to a list! This way we know that 
1336
1327
%%======================================================================
1337
1328
 
1338
1329
 
1339
 
resize_all_grid_columns(RealCol, [], ColFrameIds, MaxColWidth, MinColWidth) ->
 
1330
resize_all_grid_columns(_RealCol, [], _ColFrameIds, _MaxColWidth, _MinColWidth) ->
1340
1331
    done;
1341
1332
resize_all_grid_columns(RealCol, [ColWidth | Tail], ColFrameIds, MaxColWidth, MinColWidth) ->
1342
1333
 
1492
1483
%%======================================================================
1493
1484
 
1494
1485
 
1495
 
check_nof_cols(ColsShown, NofNewCols, ColFrameIds, ColIds, RowIds, 
1496
 
               NofRows, RowHeight, FgColor, BgColor) when NofNewCols =< 0 ->
 
1486
check_nof_cols(_ColsShown, NofNewCols, ColFrameIds, ColIds, RowIds, 
 
1487
               _NofRows, _RowHeight, _FgColor, _BgColor) when NofNewCols =< 0 ->
1497
1488
    {length(ColFrameIds), ColFrameIds, ColIds, RowIds};
1498
1489
check_nof_cols(ColsShown, NofNewCols, ColFrameIds, ColIds, 
1499
1490
               RowIds, NofRows, RowHeight, FgColor, BgColor) ->
1505
1496
       % values on these important parameters, then he can only blame himself.
1506
1497
    ParentId = lists:nth((NewColNo - 1), ColFrameIds),
1507
1498
    ParentColWidth = lists:nth((NewColNo - 1), ColsShown),
1508
 
    NewColWidth = lists:nth(NewColNo, ColsShown),
1509
1499
    Xpos = ParentColWidth + 1,
1510
1500
 
1511
1501
    {ColFrameId, LabelIds} = add_one_col_frame(ParentId, NewColNo, Xpos, FgColor, 
1671
1661
%%======================================================================
1672
1662
 
1673
1663
 
1674
 
compute_cols_shown(FirstColShown, ColWidths, GridWidth, NofCols, DefaultColWidth) ->
 
1664
compute_cols_shown(FirstColShown, ColWidths, GridWidth, _NofCols, DefaultColWidth) ->
1675
1665
    ColWidthsLength = length(ColWidths),
1676
1666
       % Normally ColWidths shall be long enough, but just to make sure...
1677
1667
       % (We could have chosen to update ColWidths here to, but right now
1755
1745
%%======================================================================
1756
1746
 
1757
1747
 
1758
 
create_col_frames(0, NofRows, RowHeight, ParentId, GridP, ColFrameAcc, LabelAcc) ->
 
1748
create_col_frames(0, _NofRows, _RowHeight, _ParentId, _GridP, ColFrameAcc, LabelAcc) ->
1759
1749
    {lists:reverse(ColFrameAcc), lists:reverse(LabelAcc)};
1760
1750
create_col_frames(N, NofRows, RowHeight, ParentId, GridP, ColFrameAcc, LabelAcc) ->
1761
1751
       % Yes, it *IS* inefficient to copy GridP for each loop.
1826
1816
    ColFrameWidth     = 1200,
1827
1817
    ColFrameHeight    = 900,
1828
1818
    Ypos = 0,
1829
 
    F = gs:frame(ParentId, [{width, ColFrameWidth},
1830
 
                            {height, ColFrameHeight},
1831
 
                            {x, Xpos},
1832
 
                            {y, Ypos},
1833
 
                            {bg, BgColor}
1834
 
                           ]).
 
1819
    gs:frame(ParentId, [{width, ColFrameWidth},
 
1820
                        {height, ColFrameHeight},
 
1821
                        {x, Xpos},
 
1822
                        {y, Ypos},
 
1823
                        {bg, BgColor}
 
1824
                       ]).
1835
1825
    
1836
1826
 
1837
1827
 
1851
1841
%%======================================================================
1852
1842
 
1853
1843
 
1854
 
create_rows_on_frame(FrameId, RowNo, NofRows, H, Y, Fg, Bg, ColNo, Acc) when RowNo > NofRows -> 
 
1844
create_rows_on_frame(_FrameId, RowNo, NofRows, _H, _Y, _Fg, _Bg, _ColNo, Acc) when RowNo > NofRows -> 
1855
1845
    lists:reverse(Acc);
1856
1846
create_rows_on_frame(FrameId, RowNo, NofRows, H, Y, Fg, Bg, ColNo, RAcc) -> 
1857
1847
    Width = 1200, 
1889
1879
%%======================================================================
1890
1880
 
1891
1881
 
1892
 
get_row_ids(0, Cols, RowAcc) ->
 
1882
get_row_ids(0, _Cols, RowAcc) ->
1893
1883
    RowAcc;
1894
1884
get_row_ids(RowNo, Cols, RowAcc) ->
1895
1885
    Row = extract_ids_for_one_row(RowNo, Cols),
1912
1902
%%======================================================================
1913
1903
 
1914
1904
 
1915
 
extract_ids_for_one_row(N, []) ->
 
1905
extract_ids_for_one_row(_N, []) ->
1916
1906
    [];
1917
1907
extract_ids_for_one_row(N, [ColIds | Tail]) ->
1918
1908
    [lists:nth(N, ColIds) | extract_ids_for_one_row(N, Tail)].
1940
1930
 
1941
1931
max(A, B) when A > B ->
1942
1932
    A;
1943
 
max(A, B) ->
 
1933
max(_, B) ->
1944
1934
    B.
1945
1935
 
1946
1936
 
1962
1952
 
1963
1953
min(A, B) when A < B ->
1964
1954
    A;
1965
 
min(A, B) ->
 
1955
min(_, B) ->
1966
1956
    B.
1967
1957