~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/wx/src/gen/glu.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2008-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2008-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
%% OPENGL UTILITY API
20
20
 
21
21
%% This file is generated DO NOT EDIT
22
22
 
23
 
%% @doc  A part of the standard OpenGL Utility api. 
 
23
%% @doc  A part of the standard OpenGL Utility api.
24
24
%% See <a href="http://www.opengl.org/sdk/docs/man/">www.opengl.org</a>
25
25
%%
26
 
%% Booleans are represented by integers 0 and 1. 
 
26
%% Booleans are represented by integers 0 and 1.
27
27
 
28
 
%% @type wx_mem(). see wx.erl on memory allocation functions
 
28
%% @type mem().    memory block
29
29
%% @type enum().   An integer defined in gl.hrl
30
30
%% @type offset(). An integer which is an offset in an array
31
 
%% @type clamp().  A float clamped between 0.0 - 1.0 
 
31
%% @type clamp().  A float clamped between 0.0 - 1.0
32
32
 
33
33
-module(glu).
34
34
-compile(inline).
35
 
-include("wxe.hrl").
36
35
-define(GLenum,32/native-unsigned).
37
36
-define(GLboolean,8/native-unsigned).
38
37
-define(GLbitfield,32/native-unsigned).
51
50
-define(GLintptr,64/native-unsigned).
52
51
-define(GLUquadric,64/native-unsigned).
53
52
-define(GLhandleARB,64/native-unsigned).
 
53
-define(GLsync,64/native-unsigned).
 
54
-define(GLuint64,64/native-unsigned).
 
55
-define(GLint64,64/native-signed).
 
56
-type enum() :: non_neg_integer().
 
57
-type mem() :: binary() | tuple().
54
58
 
55
59
-export([tesselate/2,build1DMipmapLevels/9,build1DMipmaps/6,build2DMipmapLevels/10,
56
60
  build2DMipmaps/7,build3DMipmapLevels/11,build3DMipmaps/8,checkExtension/2,
59
63
  quadricDrawStyle/2,quadricNormals/2,quadricOrientation/2,quadricTexture/2,
60
64
  scaleImage/9,sphere/4,unProject/6,unProject4/9]).
61
65
 
62
 
 
63
 
%% API 
 
66
-import(gl, [call/2,cast/2,send_bin/1]).
 
67
%% API
64
68
 
65
69
%% @spec (Vec3, [Vec3]) -> {Triangles, VertexPos}
66
70
%%  Vec3 = {float(),float(),float()}
69
73
%% @doc General purpose polygon triangulation.
70
74
%% The first argument is the normal and the second a list of
71
75
%% vertex positions. Returned is a list of indecies of the vertices
72
 
%% and a binary (64bit native float) containing an array of 
73
 
%% vertex positions, it starts with the vertices in Vs and 
 
76
%% and a binary (64bit native float) containing an array of
 
77
%% vertex positions, it starts with the vertices in Vs and
74
78
%% may contain newly created vertices in the end.
75
79
tesselate({Nx,Ny,Nz}, Vs) ->
76
 
  wxe_util:call(5000, <<(length(Vs)):32/native,0:32,
 
80
  call(5000, <<(length(Vs)):32/native,0:32,
77
81
    Nx:?GLdouble,Ny:?GLdouble,Nz:?GLdouble,
78
82
    (<< <<Vx:?GLdouble,Vy:?GLdouble,Vz:?GLdouble >>
79
83
        || {Vx,Vy,Vz} <- Vs>>)/binary >>).
80
84
 
81
85
%% @spec (Target::enum(),InternalFormat::integer(),Width::integer(),Format::enum(),Type::enum(),Level::integer(),Base::integer(),Max::integer(),Data::binary()) -> integer()
82
86
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluBuild1DMipmapLevels.xml">external</a> documentation.
 
87
-spec build1DMipmapLevels(enum(),integer(),integer(),enum(),enum(),integer(),integer(),integer(),binary()) -> integer().
83
88
build1DMipmapLevels(Target,InternalFormat,Width,Format,Type,Level,Base,Max,Data) ->
84
 
  wxe_util:send_bin(Data),
85
 
  wxe_util:call(5010, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Format:?GLenum,Type:?GLenum,Level:?GLint,Base:?GLint,Max:?GLint>>).
 
89
  send_bin(Data),
 
90
  call(5010, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Format:?GLenum,Type:?GLenum,Level:?GLint,Base:?GLint,Max:?GLint>>).
86
91
 
87
92
%% @spec (Target::enum(),InternalFormat::integer(),Width::integer(),Format::enum(),Type::enum(),Data::binary()) -> integer()
88
93
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluBuild1DMipmaps.xml">external</a> documentation.
 
94
-spec build1DMipmaps(enum(),integer(),integer(),enum(),enum(),binary()) -> integer().
89
95
build1DMipmaps(Target,InternalFormat,Width,Format,Type,Data) ->
90
 
  wxe_util:send_bin(Data),
91
 
  wxe_util:call(5011, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Format:?GLenum,Type:?GLenum>>).
 
96
  send_bin(Data),
 
97
  call(5011, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Format:?GLenum,Type:?GLenum>>).
92
98
 
93
99
%% @spec (Target::enum(),InternalFormat::integer(),Width::integer(),Height::integer(),Format::enum(),Type::enum(),Level::integer(),Base::integer(),Max::integer(),Data::binary()) -> integer()
94
100
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluBuild2DMipmapLevels.xml">external</a> documentation.
 
101
-spec build2DMipmapLevels(enum(),integer(),integer(),integer(),enum(),enum(),integer(),integer(),integer(),binary()) -> integer().
95
102
build2DMipmapLevels(Target,InternalFormat,Width,Height,Format,Type,Level,Base,Max,Data) ->
96
 
  wxe_util:send_bin(Data),
97
 
  wxe_util:call(5012, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Format:?GLenum,Type:?GLenum,Level:?GLint,Base:?GLint,Max:?GLint>>).
 
103
  send_bin(Data),
 
104
  call(5012, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Format:?GLenum,Type:?GLenum,Level:?GLint,Base:?GLint,Max:?GLint>>).
98
105
 
99
106
%% @spec (Target::enum(),InternalFormat::integer(),Width::integer(),Height::integer(),Format::enum(),Type::enum(),Data::binary()) -> integer()
100
107
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluBuild2DMipmaps.xml">external</a> documentation.
 
108
-spec build2DMipmaps(enum(),integer(),integer(),integer(),enum(),enum(),binary()) -> integer().
101
109
build2DMipmaps(Target,InternalFormat,Width,Height,Format,Type,Data) ->
102
 
  wxe_util:send_bin(Data),
103
 
  wxe_util:call(5013, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Format:?GLenum,Type:?GLenum>>).
 
110
  send_bin(Data),
 
111
  call(5013, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Format:?GLenum,Type:?GLenum>>).
104
112
 
105
113
%% @spec (Target::enum(),InternalFormat::integer(),Width::integer(),Height::integer(),Depth::integer(),Format::enum(),Type::enum(),Level::integer(),Base::integer(),Max::integer(),Data::binary()) -> integer()
106
114
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluBuild3DMipmapLevels.xml">external</a> documentation.
 
115
-spec build3DMipmapLevels(enum(),integer(),integer(),integer(),integer(),enum(),enum(),integer(),integer(),integer(),binary()) -> integer().
107
116
build3DMipmapLevels(Target,InternalFormat,Width,Height,Depth,Format,Type,Level,Base,Max,Data) ->
108
 
  wxe_util:send_bin(Data),
109
 
  wxe_util:call(5014, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Depth:?GLsizei,Format:?GLenum,Type:?GLenum,Level:?GLint,Base:?GLint,Max:?GLint>>).
 
117
  send_bin(Data),
 
118
  call(5014, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Depth:?GLsizei,Format:?GLenum,Type:?GLenum,Level:?GLint,Base:?GLint,Max:?GLint>>).
110
119
 
111
120
%% @spec (Target::enum(),InternalFormat::integer(),Width::integer(),Height::integer(),Depth::integer(),Format::enum(),Type::enum(),Data::binary()) -> integer()
112
121
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluBuild3DMipmaps.xml">external</a> documentation.
 
122
-spec build3DMipmaps(enum(),integer(),integer(),integer(),integer(),enum(),enum(),binary()) -> integer().
113
123
build3DMipmaps(Target,InternalFormat,Width,Height,Depth,Format,Type,Data) ->
114
 
  wxe_util:send_bin(Data),
115
 
  wxe_util:call(5015, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Depth:?GLsizei,Format:?GLenum,Type:?GLenum>>).
 
124
  send_bin(Data),
 
125
  call(5015, <<Target:?GLenum,InternalFormat:?GLint,Width:?GLsizei,Height:?GLsizei,Depth:?GLsizei,Format:?GLenum,Type:?GLenum>>).
116
126
 
117
 
%% @spec (ExtName::[integer()],ExtString::[integer()]) -> 0|1
 
127
%% @spec (ExtName::string(),ExtString::string()) -> 0|1
118
128
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluCheckExtension.xml">external</a> documentation.
 
129
-spec checkExtension(string(),string()) -> 0|1.
119
130
checkExtension(ExtName,ExtString) ->
120
 
  wxe_util:call(5016, <<(length(ExtName)):?GLuint,
121
 
        (<< <<C:?GLubyte>> || C <- ExtName>>)/binary,0:((8-((length(ExtName)+ 4) rem 8)) rem 8),(length(ExtString)):?GLuint,
122
 
        (<< <<C:?GLubyte>> || C <- ExtString>>)/binary,0:((8-((length(ExtString)+ 4) rem 8)) rem 8)>>).
 
131
  call(5016, <<(list_to_binary([ExtName|[0]]))/binary,0:((8-((length(ExtName)+ 1) rem 8)) rem 8),(list_to_binary([ExtString|[0]]))/binary,0:((8-((length(ExtString)+ 1) rem 8)) rem 8)>>).
123
132
 
124
133
%% @spec (Quad::integer(),Base::float(),Top::float(),Height::float(),Slices::integer(),Stacks::integer()) -> ok
125
134
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluCylinder.xml">external</a> documentation.
 
135
-spec cylinder(integer(),float(),float(),float(),integer(),integer()) -> ok.
126
136
cylinder(Quad,Base,Top,Height,Slices,Stacks) ->
127
 
  wxe_util:cast(5017, <<Quad:?GLUquadric,Base:?GLdouble,Top:?GLdouble,Height:?GLdouble,Slices:?GLint,Stacks:?GLint>>).
 
137
  cast(5017, <<Quad:?GLUquadric,Base:?GLdouble,Top:?GLdouble,Height:?GLdouble,Slices:?GLint,Stacks:?GLint>>).
128
138
 
129
139
%% @spec (Quad::integer()) -> ok
130
140
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluDeleteQuadric.xml">external</a> documentation.
 
141
-spec deleteQuadric(integer()) -> ok.
131
142
deleteQuadric(Quad) ->
132
 
  wxe_util:cast(5018, <<Quad:?GLUquadric>>).
 
143
  cast(5018, <<Quad:?GLUquadric>>).
133
144
 
134
145
%% @spec (Quad::integer(),Inner::float(),Outer::float(),Slices::integer(),Loops::integer()) -> ok
135
146
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluDisk.xml">external</a> documentation.
 
147
-spec disk(integer(),float(),float(),integer(),integer()) -> ok.
136
148
disk(Quad,Inner,Outer,Slices,Loops) ->
137
 
  wxe_util:cast(5019, <<Quad:?GLUquadric,Inner:?GLdouble,Outer:?GLdouble,Slices:?GLint,Loops:?GLint>>).
 
149
  cast(5019, <<Quad:?GLUquadric,Inner:?GLdouble,Outer:?GLdouble,Slices:?GLint,Loops:?GLint>>).
138
150
 
139
151
%% @spec (Error::enum()) -> string()
140
152
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluErrorString.xml">external</a> documentation.
 
153
-spec errorString(enum()) -> string().
141
154
errorString(Error) ->
142
 
  wxe_util:call(5020, <<Error:?GLenum>>).
 
155
  call(5020, <<Error:?GLenum>>).
143
156
 
144
157
%% @spec (Name::enum()) -> string()
145
158
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluGetString.xml">external</a> documentation.
 
159
-spec getString(enum()) -> string().
146
160
getString(Name) ->
147
 
  wxe_util:call(5021, <<Name:?GLenum>>).
 
161
  call(5021, <<Name:?GLenum>>).
148
162
 
149
163
%% @spec (EyeX::float(),EyeY::float(),EyeZ::float(),CenterX::float(),CenterY::float(),CenterZ::float(),UpX::float(),UpY::float(),UpZ::float()) -> ok
150
164
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluLookAt.xml">external</a> documentation.
 
165
-spec lookAt(float(),float(),float(),float(),float(),float(),float(),float(),float()) -> ok.
151
166
lookAt(EyeX,EyeY,EyeZ,CenterX,CenterY,CenterZ,UpX,UpY,UpZ) ->
152
 
  wxe_util:cast(5022, <<EyeX:?GLdouble,EyeY:?GLdouble,EyeZ:?GLdouble,CenterX:?GLdouble,CenterY:?GLdouble,CenterZ:?GLdouble,UpX:?GLdouble,UpY:?GLdouble,UpZ:?GLdouble>>).
 
167
  cast(5022, <<EyeX:?GLdouble,EyeY:?GLdouble,EyeZ:?GLdouble,CenterX:?GLdouble,CenterY:?GLdouble,CenterZ:?GLdouble,UpX:?GLdouble,UpY:?GLdouble,UpZ:?GLdouble>>).
153
168
 
154
169
%% @spec () -> integer()
155
170
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluNewQuadric.xml">external</a> documentation.
 
171
-spec newQuadric() -> integer().
156
172
newQuadric() ->
157
 
  wxe_util:call(5023, <<>>).
 
173
  call(5023, <<>>).
158
174
 
159
175
%% @spec (Left::float(),Right::float(),Bottom::float(),Top::float()) -> ok
160
176
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluOrtho2D.xml">external</a> documentation.
 
177
-spec ortho2D(float(),float(),float(),float()) -> ok.
161
178
ortho2D(Left,Right,Bottom,Top) ->
162
 
  wxe_util:cast(5024, <<Left:?GLdouble,Right:?GLdouble,Bottom:?GLdouble,Top:?GLdouble>>).
 
179
  cast(5024, <<Left:?GLdouble,Right:?GLdouble,Bottom:?GLdouble,Top:?GLdouble>>).
163
180
 
164
181
%% @spec (Quad::integer(),Inner::float(),Outer::float(),Slices::integer(),Loops::integer(),Start::float(),Sweep::float()) -> ok
165
182
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluPartialDisk.xml">external</a> documentation.
 
183
-spec partialDisk(integer(),float(),float(),integer(),integer(),float(),float()) -> ok.
166
184
partialDisk(Quad,Inner,Outer,Slices,Loops,Start,Sweep) ->
167
 
  wxe_util:cast(5025, <<Quad:?GLUquadric,Inner:?GLdouble,Outer:?GLdouble,Slices:?GLint,Loops:?GLint,Start:?GLdouble,Sweep:?GLdouble>>).
 
185
  cast(5025, <<Quad:?GLUquadric,Inner:?GLdouble,Outer:?GLdouble,Slices:?GLint,Loops:?GLint,Start:?GLdouble,Sweep:?GLdouble>>).
168
186
 
169
187
%% @spec (Fovy::float(),Aspect::float(),ZNear::float(),ZFar::float()) -> ok
170
188
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluPerspective.xml">external</a> documentation.
 
189
-spec perspective(float(),float(),float(),float()) -> ok.
171
190
perspective(Fovy,Aspect,ZNear,ZFar) ->
172
 
  wxe_util:cast(5026, <<Fovy:?GLdouble,Aspect:?GLdouble,ZNear:?GLdouble,ZFar:?GLdouble>>).
 
191
  cast(5026, <<Fovy:?GLdouble,Aspect:?GLdouble,ZNear:?GLdouble,ZFar:?GLdouble>>).
173
192
 
174
 
%% @spec (X::float(),Y::float(),DelX::float(),DelY::float(),Viewport::{integer()}) -> ok
 
193
%% @spec (X::float(),Y::float(),DelX::float(),DelY::float(),Viewport::{integer(),integer(),integer(),integer()}) -> ok
175
194
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluPickMatrix.xml">external</a> documentation.
 
195
-spec pickMatrix(float(),float(),float(),float(),{integer(),integer(),integer(),integer()}) -> ok.
176
196
pickMatrix(X,Y,DelX,DelY,{V1,V2,V3,V4}) ->
177
 
  wxe_util:cast(5027, <<X:?GLdouble,Y:?GLdouble,DelX:?GLdouble,DelY:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>).
 
197
  cast(5027, <<X:?GLdouble,Y:?GLdouble,DelX:?GLdouble,DelY:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>).
178
198
 
179
 
%% @spec (ObjX::float(),ObjY::float(),ObjZ::float(),Model::{float()},Proj::{float()},View::{integer()}) -> {integer(),WinX::float(),WinY::float(),WinZ::float()}
 
199
%% @spec (ObjX::float(),ObjY::float(),ObjZ::float(),Model::{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},Proj::{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},View::{integer(),integer(),integer(),integer()}) -> {integer(),WinX::float(),WinY::float(),WinZ::float()}
180
200
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluProject.xml">external</a> documentation.
 
201
-spec project(float(),float(),float(),{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},{integer(),integer(),integer(),integer()}) -> {integer(),float(),float(),float()}.
181
202
project(ObjX,ObjY,ObjZ,{M1,M2,M3,M4,M5,M6,M7,M8,M9,M10,M11,M12,M13,M14,M15,M16},{P1,P2,P3,P4,P5,P6,P7,P8,P9,P10,P11,P12,P13,P14,P15,P16},{V1,V2,V3,V4}) ->
182
 
  wxe_util:call(5028, <<ObjX:?GLdouble,ObjY:?GLdouble,ObjZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,M13:?GLdouble,M14:?GLdouble,M15:?GLdouble,M16:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,P13:?GLdouble,P14:?GLdouble,P15:?GLdouble,P16:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>);
 
203
  call(5028, <<ObjX:?GLdouble,ObjY:?GLdouble,ObjZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,M13:?GLdouble,M14:?GLdouble,M15:?GLdouble,M16:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,P13:?GLdouble,P14:?GLdouble,P15:?GLdouble,P16:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>);
183
204
project(ObjX,ObjY,ObjZ,{M1,M2,M3,M4,M5,M6,M7,M8,M9,M10,M11,M12},{P1,P2,P3,P4,P5,P6,P7,P8,P9,P10,P11,P12},{V1,V2,V3,V4}) ->
184
 
  wxe_util:call(5028, <<ObjX:?GLdouble,ObjY:?GLdouble,ObjZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,0:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,0:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,0:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,1:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,0:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,0:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,0:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,1:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>).
 
205
  call(5028, <<ObjX:?GLdouble,ObjY:?GLdouble,ObjZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,0:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,0:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,0:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,1:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,0:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,0:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,0:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,1:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>).
185
206
 
186
207
%% @spec (Quad::integer(),Draw::enum()) -> ok
187
208
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluQuadricDrawStyle.xml">external</a> documentation.
 
209
-spec quadricDrawStyle(integer(),enum()) -> ok.
188
210
quadricDrawStyle(Quad,Draw) ->
189
 
  wxe_util:cast(5029, <<Quad:?GLUquadric,Draw:?GLenum>>).
 
211
  cast(5029, <<Quad:?GLUquadric,Draw:?GLenum>>).
190
212
 
191
213
%% @spec (Quad::integer(),Normal::enum()) -> ok
192
214
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluQuadricNormals.xml">external</a> documentation.
 
215
-spec quadricNormals(integer(),enum()) -> ok.
193
216
quadricNormals(Quad,Normal) ->
194
 
  wxe_util:cast(5030, <<Quad:?GLUquadric,Normal:?GLenum>>).
 
217
  cast(5030, <<Quad:?GLUquadric,Normal:?GLenum>>).
195
218
 
196
219
%% @spec (Quad::integer(),Orientation::enum()) -> ok
197
220
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluQuadricOrientation.xml">external</a> documentation.
 
221
-spec quadricOrientation(integer(),enum()) -> ok.
198
222
quadricOrientation(Quad,Orientation) ->
199
 
  wxe_util:cast(5031, <<Quad:?GLUquadric,Orientation:?GLenum>>).
 
223
  cast(5031, <<Quad:?GLUquadric,Orientation:?GLenum>>).
200
224
 
201
225
%% @spec (Quad::integer(),Texture::0|1) -> ok
202
226
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluQuadricTexture.xml">external</a> documentation.
 
227
-spec quadricTexture(integer(),0|1) -> ok.
203
228
quadricTexture(Quad,Texture) ->
204
 
  wxe_util:cast(5032, <<Quad:?GLUquadric,Texture:?GLboolean>>).
 
229
  cast(5032, <<Quad:?GLUquadric,Texture:?GLboolean>>).
205
230
 
206
 
%% @spec (Format::enum(),WIn::integer(),HIn::integer(),TypeIn::enum(),DataIn::binary(),WOut::integer(),HOut::integer(),TypeOut::enum(),DataOut::wx:wx_mem()) -> integer()
 
231
%% @spec (Format::enum(),WIn::integer(),HIn::integer(),TypeIn::enum(),DataIn::binary(),WOut::integer(),HOut::integer(),TypeOut::enum(),DataOut::mem()) -> integer()
207
232
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluScaleImage.xml">external</a> documentation.
 
233
-spec scaleImage(enum(),integer(),integer(),enum(),binary(),integer(),integer(),enum(),mem()) -> integer().
208
234
scaleImage(Format,WIn,HIn,TypeIn,DataIn,WOut,HOut,TypeOut,DataOut) ->
209
 
  wxe_util:send_bin(DataIn),
210
 
  wxe_util:send_bin(DataOut#wx_mem.bin),
211
 
  wxe_util:call(5033, <<Format:?GLenum,WIn:?GLsizei,HIn:?GLsizei,TypeIn:?GLenum,WOut:?GLsizei,HOut:?GLsizei,TypeOut:?GLenum>>).
 
235
  send_bin(DataIn),
 
236
  send_bin(DataOut),
 
237
  call(5033, <<Format:?GLenum,WIn:?GLsizei,HIn:?GLsizei,TypeIn:?GLenum,WOut:?GLsizei,HOut:?GLsizei,TypeOut:?GLenum>>).
212
238
 
213
239
%% @spec (Quad::integer(),Radius::float(),Slices::integer(),Stacks::integer()) -> ok
214
240
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluSphere.xml">external</a> documentation.
 
241
-spec sphere(integer(),float(),integer(),integer()) -> ok.
215
242
sphere(Quad,Radius,Slices,Stacks) ->
216
 
  wxe_util:cast(5034, <<Quad:?GLUquadric,Radius:?GLdouble,Slices:?GLint,Stacks:?GLint>>).
 
243
  cast(5034, <<Quad:?GLUquadric,Radius:?GLdouble,Slices:?GLint,Stacks:?GLint>>).
217
244
 
218
 
%% @spec (WinX::float(),WinY::float(),WinZ::float(),Model::{float()},Proj::{float()},View::{integer()}) -> {integer(),ObjX::float(),ObjY::float(),ObjZ::float()}
 
245
%% @spec (WinX::float(),WinY::float(),WinZ::float(),Model::{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},Proj::{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},View::{integer(),integer(),integer(),integer()}) -> {integer(),ObjX::float(),ObjY::float(),ObjZ::float()}
219
246
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluUnProject.xml">external</a> documentation.
 
247
-spec unProject(float(),float(),float(),{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},{integer(),integer(),integer(),integer()}) -> {integer(),float(),float(),float()}.
220
248
unProject(WinX,WinY,WinZ,{M1,M2,M3,M4,M5,M6,M7,M8,M9,M10,M11,M12,M13,M14,M15,M16},{P1,P2,P3,P4,P5,P6,P7,P8,P9,P10,P11,P12,P13,P14,P15,P16},{V1,V2,V3,V4}) ->
221
 
  wxe_util:call(5035, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,M13:?GLdouble,M14:?GLdouble,M15:?GLdouble,M16:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,P13:?GLdouble,P14:?GLdouble,P15:?GLdouble,P16:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>);
 
249
  call(5035, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,M13:?GLdouble,M14:?GLdouble,M15:?GLdouble,M16:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,P13:?GLdouble,P14:?GLdouble,P15:?GLdouble,P16:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>);
222
250
unProject(WinX,WinY,WinZ,{M1,M2,M3,M4,M5,M6,M7,M8,M9,M10,M11,M12},{P1,P2,P3,P4,P5,P6,P7,P8,P9,P10,P11,P12},{V1,V2,V3,V4}) ->
223
 
  wxe_util:call(5035, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,0:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,0:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,0:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,1:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,0:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,0:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,0:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,1:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>).
 
251
  call(5035, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,0:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,0:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,0:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,1:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,0:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,0:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,0:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,1:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint>>).
224
252
 
225
 
%% @spec (WinX::float(),WinY::float(),WinZ::float(),ClipW::float(),Model::{float()},Proj::{float()},View::{integer()},NearVal::float(),FarVal::float()) -> {integer(),ObjX::float(),ObjY::float(),ObjZ::float(),ObjW::float()}
 
253
%% @spec (WinX::float(),WinY::float(),WinZ::float(),ClipW::float(),Model::{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},Proj::{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},View::{integer(),integer(),integer(),integer()},NearVal::float(),FarVal::float()) -> {integer(),ObjX::float(),ObjY::float(),ObjZ::float(),ObjW::float()}
226
254
%% @doc See <a href="http://www.opengl.org/sdk/docs/man/xhtml/gluUnProject.xml">external</a> documentation.
 
255
-spec unProject4(float(),float(),float(),float(),{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},{float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float(),float()},{integer(),integer(),integer(),integer()},float(),float()) -> {integer(),float(),float(),float(),float()}.
227
256
unProject4(WinX,WinY,WinZ,ClipW,{M1,M2,M3,M4,M5,M6,M7,M8,M9,M10,M11,M12,M13,M14,M15,M16},{P1,P2,P3,P4,P5,P6,P7,P8,P9,P10,P11,P12,P13,P14,P15,P16},{V1,V2,V3,V4},NearVal,FarVal) ->
228
 
  wxe_util:call(5036, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,ClipW:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,M13:?GLdouble,M14:?GLdouble,M15:?GLdouble,M16:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,P13:?GLdouble,P14:?GLdouble,P15:?GLdouble,P16:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint,NearVal:?GLdouble,FarVal:?GLdouble>>);
 
257
  call(5036, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,ClipW:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,M13:?GLdouble,M14:?GLdouble,M15:?GLdouble,M16:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,P13:?GLdouble,P14:?GLdouble,P15:?GLdouble,P16:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint,NearVal:?GLdouble,FarVal:?GLdouble>>);
229
258
unProject4(WinX,WinY,WinZ,ClipW,{M1,M2,M3,M4,M5,M6,M7,M8,M9,M10,M11,M12},{P1,P2,P3,P4,P5,P6,P7,P8,P9,P10,P11,P12},{V1,V2,V3,V4},NearVal,FarVal) ->
230
 
  wxe_util:call(5036, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,ClipW:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,0:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,0:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,0:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,1:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,0:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,0:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,0:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,1:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint,NearVal:?GLdouble,FarVal:?GLdouble>>).
 
259
  call(5036, <<WinX:?GLdouble,WinY:?GLdouble,WinZ:?GLdouble,ClipW:?GLdouble,M1:?GLdouble,M2:?GLdouble,M3:?GLdouble,0:?GLdouble,M4:?GLdouble,M5:?GLdouble,M6:?GLdouble,0:?GLdouble,M7:?GLdouble,M8:?GLdouble,M9:?GLdouble,0:?GLdouble,M10:?GLdouble,M11:?GLdouble,M12:?GLdouble,1:?GLdouble,P1:?GLdouble,P2:?GLdouble,P3:?GLdouble,0:?GLdouble,P4:?GLdouble,P5:?GLdouble,P6:?GLdouble,0:?GLdouble,P7:?GLdouble,P8:?GLdouble,P9:?GLdouble,0:?GLdouble,P10:?GLdouble,P11:?GLdouble,P12:?GLdouble,1:?GLdouble,V1:?GLint,V2:?GLint,V3:?GLint,V4:?GLint,NearVal:?GLdouble,FarVal:?GLdouble>>).
231
260