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

« back to all changes in this revision

Viewing changes to lib/wx/examples/demo/ex_grid.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
 
 
19
-module(ex_grid).
 
20
 
 
21
-behavoiur(wx_object).
 
22
 
 
23
%% Client API
 
24
-export([start/1]).
 
25
 
 
26
%% wx_object callbacks
 
27
-export([init/1, terminate/2,  code_change/3,
 
28
         handle_info/2, handle_call/3, handle_event/2]).
 
29
 
 
30
-include_lib("wx/include/wx.hrl").
 
31
 
 
32
-record(state, 
 
33
        {
 
34
          parent,
 
35
          config
 
36
        }).
 
37
 
 
38
start(Config) ->
 
39
    wx_object:start_link(?MODULE, Config, []).
 
40
 
 
41
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
42
init(Config) ->
 
43
    wx:batch(fun() -> do_init(Config) end).
 
44
 
 
45
do_init(Config) ->
 
46
    Parent = proplists:get_value(parent, Config),  
 
47
    Panel = wxPanel:new(Parent, []),
 
48
 
 
49
    %% Setup sizers
 
50
    MainSizer = wxBoxSizer:new(?wxVERTICAL),
 
51
    Sizer = wxStaticBoxSizer:new(?wxVERTICAL, Panel, 
 
52
                                 [{label, "wxGrid"}]),
 
53
    Grid1 = create_grid1(Panel),
 
54
    %% Add to sizers
 
55
    Options = [{flag, ?wxEXPAND}, {proportion, 1}],
 
56
 
 
57
    wxSizer:add(Sizer, Grid1, Options),
 
58
    wxSizer:add(MainSizer, Sizer, Options),
 
59
 
 
60
    wxPanel:setSizer(Panel, MainSizer),
 
61
    {Panel, #state{parent=Panel, config=Config}}.
 
62
 
 
63
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
64
%% Callbacks handled as normal gen_server callbacks
 
65
handle_info(Msg, State) ->
 
66
    demo:format(State#state.config, "Got Info ~p\n", [Msg]),
 
67
    {noreply, State}.
 
68
 
 
69
handle_call(Msg, _From, State) ->
 
70
    demo:format(State#state.config, "Got Call ~p\n", [Msg]),
 
71
    {reply,{error, nyi}, State}.
 
72
 
 
73
%% Async Events are handled in handle_event as in handle_info
 
74
handle_event(Ev = #wx{}, State = #state{}) ->
 
75
    demo:format(State#state.config, "Got Event ~p\n", [Ev]),
 
76
    {noreply, State}.
 
77
 
 
78
code_change(_, _, State) ->
 
79
    {stop, ignore, State}.
 
80
 
 
81
terminate(_Reason, _State) ->
 
82
    ok.
 
83
 
 
84
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
85
%% Local functions
 
86
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
87
 
 
88
create_grid1(Panel) ->
 
89
    Grid = wxGrid:new(Panel, 2, []),
 
90
    wxGrid:createGrid(Grid, 100, 5),
 
91
    Font = wxFont:new(16, ?wxFONTFAMILY_SWISS,
 
92
                      ?wxFONTSTYLE_NORMAL,
 
93
                      ?wxFONTWEIGHT_NORMAL, []),
 
94
    Fun =
 
95
        fun(Int) ->
 
96
                wxGrid:setCellValue(Grid, Int, 0, "Value"),
 
97
                wxGrid:setCellValue(Grid, Int, 1, "Value"),
 
98
                wxGrid:setCellValue(Grid, Int, 2, "Value"),
 
99
                wxGrid:setCellValue(Grid, Int, 3, "Read only"),
 
100
                wxGrid:setCellTextColour(Grid, Int, 3, ?wxWHITE),
 
101
                wxGrid:setReadOnly(Grid, Int, 3, [{isReadOnly,true}]),
 
102
                wxGrid:setCellValue(Grid, Int, 4, "Value"),
 
103
                case Int rem 4 of
 
104
                    0 -> wxGrid:setCellBackgroundColour(Grid, Int, 3, ?wxRED);
 
105
                    1 -> wxGrid:setCellBackgroundColour(Grid, Int, 3, ?wxGREEN),
 
106
                         wxGrid:setCellTextColour(Grid, Int, 2, {255,215,0,255});
 
107
                    2 -> wxGrid:setCellBackgroundColour(Grid, Int, 3, ?wxBLUE);
 
108
                    _ -> wxGrid:setCellBackgroundColour(Grid, Int, 1, ?wxCYAN),
 
109
                         wxGrid:setCellValue(Grid, Int, 1,
 
110
                                             "Centered\nhorizontally"),
 
111
                         wxGrid:setCellAlignment(Grid, Int, 4,
 
112
                                                 0,?wxALIGN_CENTER),
 
113
                         wxGrid:setCellValue(Grid, Int, 4,
 
114
                                             "Centered\nvertically"),
 
115
                         wxGrid:setCellAlignment(Grid, Int, 1,
 
116
                                                 ?wxALIGN_CENTER,0),
 
117
                         wxGrid:setCellTextColour(Grid, Int, 3, ?wxBLACK),
 
118
                         wxGrid:setCellAlignment(Grid, Int, 2,
 
119
                                                 ?wxALIGN_CENTER,
 
120
                                                 ?wxALIGN_CENTER),
 
121
                         wxGrid:setCellFont(Grid, Int, 0, Font),
 
122
                         wxGrid:setCellValue(Grid, Int, 2,
 
123
                                             "Centered vertically\nand horizontally"),
 
124
                         wxGrid:setRowSize(Grid, Int, 80)
 
125
                end
 
126
        end,
 
127
    wx:foreach(Fun, lists:seq(0,99)),
 
128
    wxGrid:setColSize(Grid, 2, 150),
 
129
    wxGrid:connect(Grid, grid_cell_change),
 
130
    Grid.
 
131
 
 
132