Mercurial > pub > dyncall > bindings
comparison R/scratch/structs.R @ 0:0cfcc391201f
initial from svn dyncall-1745
author | Daniel Adler |
---|---|
date | Thu, 19 Mar 2015 22:26:28 +0100 |
parents | |
children |
comparison
equal
deleted
inserted
replaced
-1:000000000000 | 0:0cfcc391201f |
---|---|
1 # struct tests: | |
2 | |
3 | |
4 # test embedded structures and inline assignments | |
5 | |
6 parseStructInfos(" | |
7 SDL_Rect{ssSS}x y w h ; | |
8 Test{II<SDL_Rect>II}a b rect c d; | |
9 ") | |
10 x <- new.struct("Test") | |
11 print(x) | |
12 | |
13 r <- new.struct("SDL_Rect") | |
14 r$x <- 1 | |
15 r$y <- 2 | |
16 r$w <- 3 | |
17 r$h <- 4 | |
18 x$rect <- r | |
19 | |
20 # | |
21 | |
22 parseStructInfos(" | |
23 SDL_ActiveEvent{CCC}type gain state ; | |
24 SDL_keysym{CiiS}scancode sym mod unicode ; | |
25 SDL_KeyboardEvent{CCC<SDL_keysym>}type which state keysym ; | |
26 SDL_MouseMotionEvent{CCCSSss}type which state x y xrel yrel ; | |
27 SDL_MouseButtonEvent{CCCCSS}type which button state x y ; | |
28 ") | |
29 | |
30 g | |
31 | |
32 new <- function() | |
33 { | |
34 x <- list() | |
35 class(x) <- "test" | |
36 return(x) | |
37 } | |
38 | |
39 "$<-.test" <- function(x, index, value) | |
40 { | |
41 cat("$<-\n") | |
42 cat("nargs:", nargs(), "\n" ) | |
43 x[index] <- value | |
44 return(x) | |
45 } | |
46 | |
47 "$.test" <- function(x, index) | |
48 { | |
49 cat("$\n") | |
50 x[index] | |
51 } | |
52 | |
53 x <- new() | |
54 x$a <- 23 | |
55 | |
56 x$a$b <- 23 | |
57 | |
58 | |
59 | |
60 | |
61 str(x) | |
62 | |
63 x$rect | |
64 | |
65 registerStructInfos(" | |
66 SDL_Rect{ssSS}x y w h ; | |
67 SDL_Surface{I*<SDL_PixelFormat>iiS*vi*<private_hwdata><SDL_Rect>II*<SDL_BlitMap>Ii}flags format w h pitch pixels offset hwdata clip_rect unused1 locked map format_version refcount ; | |
68 ") | |
69 | |
70 | |
71 x <- new.struct("SDL_Rect") | |
72 x$x <- 10 | |
73 x$y <- 10 | |
74 x$w <- 100 | |
75 x$h <- 100 | |
76 str(x) | |
77 | |
78 # ---------------------------------------------------------------------------- | |
79 # tests | |
80 | |
81 | |
82 registerStructInfos("SDL_SysWMmsg{}; | |
83 SDL_SysWMEvent{C*<SDL_SysWMmsg>}type msg ; | |
84 ") | |
85 | |
86 registerStructInfos(sdlStructs) | |
87 parseStructInfos("SDL_UserEvent{Ci*v*v}type code data1 data2 ;SDL_QuitEvent{C}type ;") | |
88 sigs <- "SDL_UserEvent{Ci*v*v}type code data1 data2 ;SDL_QuitEvent{C}type ;" | |
89 | |
90 for (i in seq(along=sigs)) | |
91 { | |
92 if ( length(sigs[[i]]) < 2 ) next | |
93 name <- sigs[[i]][[1]] | |
94 # eat white spaces | |
95 name <- gsub("[ \n\t]*","",name) | |
96 tail <- unlist( strsplit(sigs[[i]][[2]], "\\}") ) | |
97 sig <- tail[[1]] | |
98 fields <- unlist( strsplit( tail[[2]], "[ \n\t]+" ) ) | |
99 infos[[name]] <- list(sig, fields) | |
100 infos[[name]] <- makeStructInfo(sig, fields) | |
101 } | |
102 return(infos) | |
103 } | |
104 | |
105 | |
106 | |
107 | |
108 registerStructInfos("SDL_version{CCC}major minor patch ; | |
109 _SDL_TimerID{}; | |
110 SDL_SysWMmsg{}; | |
111 SDL_SysWMEvent{C*<SDL_SysWMmsg>}type msg ; | |
112 SDL_UserEvent{Ci*v*v}type code data1 data2 ; | |
113 SDL_QuitEvent{C}type ; | |
114 SDL_ExposeEvent{C}type ; | |
115 SDL_ResizeEvent{Cii}type w h ; | |
116 SDL_JoyButtonEvent{CCCC}type which button state ; | |
117 SDL_JoyHatEvent{CCCC}type which hat value ; | |
118 SDL_JoyBallEvent{CCCss}type which ball xrel yrel ; | |
119 SDL_JoyAxisEvent{CCCs}type which axis value ; | |
120 SDL_MouseButtonEvent{CCCCSS}type which button state x y ; | |
121 SDL_MouseMotionEvent{CCCSSss}type which state x y xrel yrel ; | |
122 SDL_keysym{CiiS}scancode sym mod unicode ; | |
123 SDL_KeyboardEvent{CCC<SDL_keysym>}type which state keysym ; | |
124 SDL_ActiveEvent{CCC}type gain state ; | |
125 SDL_Rect{ssSS}x y w h ; | |
126 SDL_Surface{I*<SDL_PixelFormat>iiS*vi*<private_hwdata><SDL_Rect>II*<SDL_BlitMap>Ii}flags format w h pitch pixels offset hwdata clip_rect unused1 locked map format_version refcount ; | |
127 ") | |
128 | |
129 | |
130 | |
131 sigs <- "SDL_ActiveEvent{CCC}type gain state ;SDL_AudioCVT{iSSd*Ciiidi}needed src_format dst_format rate_incr buf len len_cvt len_mult len_ratio filters filter_index ;" | |
132 sigs <- "SDL_AudioCVT{iSSd*Ciiidi}needed src_format dst_format rate_incr buf len len_cvt len_mult len_ratio filters filter_index ;" | |
133 parseStructInfos(sigs) | |
134 dsadsigs <- sdlStructs | |
135 sdlStructs <- " | |
136 SDL_version{CCC}major minor patch ; | |
137 _SDL_TimerID{}; | |
138 SDL_SysWMmsg{}; | |
139 SDL_SysWMEvent{C*<SDL_SysWMmsg>}type msg ; | |
140 SDL_UserEvent{Ci*v*v}type code data1 data2 ; | |
141 SDL_QuitEvent{C}type ; | |
142 SDL_ExposeEvent{C}type ; | |
143 SDL_ResizeEvent{Cii}type w h ; | |
144 SDL_JoyButtonEvent{CCCC}type which button state ; | |
145 SDL_JoyHatEvent{CCCC}type which hat value ; | |
146 SDL_JoyBallEvent{CCCss}type which ball xrel yrel ; | |
147 SDL_JoyAxisEvent{CCCs}type which axis value ; | |
148 SDL_MouseButtonEvent{CCCCSS}type which button state x y ; | |
149 SDL_MouseMotionEvent{CCCSSss}type which state x y xrel yrel ; | |
150 SDL_keysym{CiiS}scancode sym mod unicode ; | |
151 SDL_KeyboardEvent{CCC<SDL_keysym>}type which state keysym ; | |
152 SDL_ActiveEvent{CCC}type gain state ; | |
153 _SDL_Joystick{}; | |
154 SDL_Rect{ssSS}x y w h ; | |
155 WMcursor{}; | |
156 SDL_Cursor{<SDL_Rect>ss*C*C*<WMcursor>}area hot_x hot_y data mask save wm_cursor ; | |
157 SDL_Overlay{Iiii*S**<private_yuvhwfuncs>*<private_yuvhwdata>II}format w h planes pitches pixels hwfuncs hwdata hw_overlay UnusedBits ; | |
158 private_yuvhwdata{}; | |
159 private_yuvhwfuncs{}; | |
160 SDL_VideoInfo{IIIIIIIIIIIII*<SDL_PixelFormat>ii}hw_available wm_available UnusedBits1 UnusedBits2 blit_hw blit_hw_CC blit_hw_A blit_sw blit_sw_CC blit_sw_A blit_fill UnusedBits3 video_mem vfmt current_w current_h ; | |
161 SDL_BlitMap{}; | |
162 private_hwdata{}; | |
163 SDL_Color{CCCC}r g b unused ; | |
164 SDL_Palette{i*<SDL_Color>}ncolors colors ; | |
165 SDL_PixelFormat{*<SDL_Palette>CCCCCCCCCCIIIIIC}palette BitsPerPixel BytesPerPixel Rloss Gloss Bloss Aloss Rshift Gshift Bshift Ashift Rmask Gmask Bmask Amask colorkey alpha ; | |
166 SDL_CD{iiiii}id status numtracks cur_track cur_frame track ; | |
167 SDL_CDtrack{CCSII}id type unused length offset ; | |
168 SDL_AudioCVT{iSSd*Ciiidi}needed src_format dst_format rate_incr buf len len_cvt len_mult len_ratio filters filter_index ; | |
169 SDL_AudioSpec{iSCCSSI*p*v}freq format channels silence samples padding size callback userdata ; | |
170 " | |
171 | |
172 | |
173 | |
174 old <- "SDL_version{CCC}major minor patch ; | |
175 _SDL_TimerID{}; | |
176 SDL_SysWMEvent{C*<SDL_SysWMmsg>}type msg ; | |
177 SDL_SysWMmsg{}; | |
178 SDL_UserEvent{Ci*v*v}type code data1 data2 ; | |
179 SDL_QuitEvent{C}type ; | |
180 SDL_ExposeEvent{C}type ; | |
181 SDL_ResizeEvent{Cii}type w h ; | |
182 SDL_JoyButtonEvent{CCCC}type which button state ; | |
183 SDL_JoyHatEvent{CCCC}type which hat value ; | |
184 SDL_JoyBallEvent{CCCss}type which ball xrel yrel ; | |
185 SDL_JoyAxisEvent{CCCs}type which axis value ; | |
186 SDL_MouseButtonEvent{CCCCSS}type which button state x y ; | |
187 SDL_MouseMotionEvent{CCCSSss}type which state x y xrel yrel ; | |
188 SDL_KeyboardEvent{CCC<SDL_keysym>}type which state keysym ; | |
189 SDL_ActiveEvent{CCC}type gain state ; | |
190 _SDL_Joystick{}; | |
191 SDL_Cursor{<SDL_Rect>ss*C*C*<WMcursor>}area hot_x hot_y data mask save wm_cursor ; | |
192 WMcursor{}; | |
193 SDL_Overlay{Iiii*S**<private_yuvhwfuncs>*<private_yuvhwdata>II}format w h planes pitches pixels hwfuncs hwdata hw_overlay UnusedBits ; | |
194 private_yuvhwdata{}; | |
195 private_yuvhwfuncs{}; | |
196 SDL_VideoInfo{IIIIIIIIIIIII*<SDL_PixelFormat>ii}hw_available wm_available UnusedBits1 UnusedBits2 blit_hw blit_hw_CC blit_hw_A blit_sw blit_sw_CC blit_sw_A blit_fill UnusedBits3 video_mem vfmt current_w current_h ; | |
197 SDL_Surface{I*<SDL_PixelFormat>iiS*vi*<private_hwdata><SDL_Rect>II*<SDL_BlitMap>Ii}flags format w h pitch pixels offset hwdata clip_rect unused1 locked map format_version refcount ; | |
198 SDL_BlitMap{}; | |
199 private_hwdata{}; | |
200 SDL_PixelFormat{*<SDL_Palette>CCCCCCCCCCIIIIIC}palette BitsPerPixel BytesPerPixel Rloss Gloss Bloss Aloss Rshift Gshift Bshift Ashift Rmask Gmask Bmask Amask colorkey alpha ; | |
201 SDL_Palette{i*<SDL_Color>}ncolors colors ; | |
202 SDL_Color{CCCC}r g b unused ; | |
203 SDL_Rect{ssSS}x y w h ; | |
204 SDL_keysym{CiiS}scancode sym mod unicode ; | |
205 SDL_CD{iiiii}id status numtracks cur_track cur_frame track ; | |
206 SDL_CDtrack{CCSII}id type unused length offset ; | |
207 SDL_AudioCVT{iSSd*Ciiidi}needed src_format dst_format rate_incr buf len len_cvt len_mult len_ratio filters filter_index ; | |
208 SDL_AudioSpec{iSCCSSI*p*v}freq format channels silence samples padding size callback userdata ; | |
209 SDL_RWops{*p*p*p*pI<$_7>}seek read write close type hidden ; | |
210 SDL_Thread{}; | |
211 SDL_cond{}; | |
212 SDL_semaphore{}; | |
213 SDL_mutex{}; | |
214 _SDL_iconv_t{}; | |
215 lldiv_t{ll}quot rem ; | |
216 ldiv_t{jj}quot rem ; | |
217 div_t{ii}quot rem ; | |
218 _iobuf{*ci*ciiii*c}_ptr _cnt _base _flag _file _charbuf _bufsiz _tmpfname ; | |
219 $_8{i*v<$_9>}append h buffer ; | |
220 $_10{i*<_iobuf>}autoclose fp ; | |
221 $_11{*C*C*C}base here stop ; | |
222 $_12{*v}data1 ; | |
223 $_9{*vii}data size left ; | |
224 " | |
225 | |
226 | |
227 .types <- list() | |
228 | |
229 setStruct <- function(name, ...) | |
230 { | |
231 x <- list(...) | |
232 class(x) <- c("struct","type") | |
233 .types[[name]] <<- x | |
234 } | |
235 | |
236 setUnion <- function(name, ...) | |
237 { | |
238 x <- list(...) | |
239 class(x) <- c("union","type") | |
240 .types[[name]] <<- x | |
241 } | |
242 | |
243 getType <- function(name) | |
244 { | |
245 .types[[name]] | |
246 } | |
247 | |
248 | |
249 setStruct("SDL_keysym", scancode="C", sym="i", mod="i", unicode="S" ) | |
250 setStruct("SDL_KeyboardEvent", type="C", which="C", state="C", keysym="{SDL_keysym}") | |
251 | |
252 parseTypeSignature("SDL_Event|C<SDL_ActiveEvent><SDL_KeyboardEvent><SDL_MouseMotionEvent><SDL_MouseButtonEvent><SDL_JoyAxisEvent><SDL_JoyBallEvent><SDL_JoyHatEvent><SDL_JoyButtonEvent><SDL_ResizeEvent><SDL_ExposeEvent><SDL_QuitEvent><SDL_UserEvent><SDL_SysWMEvent>|type active key motion button jaxis jball jhat jbutton resize expose quit user syswm ;") | |
253 | |
254 setUnion("SDL_Event", | |
255 type="uchar", | |
256 action="SDL_ActiveEvent", | |
257 key="SDL_KeyboardEvent", | |
258 motion="SDL_MouseMotionEvent", | |
259 button="SDL_MouseButtonEvent", | |
260 jaxis="SDL_JoyAxisEvent", | |
261 jball="SDL_JoyBallEvent", | |
262 jbutton="SDL_JoyButtonEvent", | |
263 resize="SDL_ResizeEvent", | |
264 expose="SDL_ExposeEvent", | |
265 quit="SDL_QuitEvent", | |
266 user="SDL_UserEvent", | |
267 syswm="SDL_SysWMEvent") | |
268 | |
269 .sizeof <- c( | |
270 B=.Machine$sizeof.long, | |
271 c=1L, | |
272 C=1L, | |
273 s=2L, | |
274 S=2L, | |
275 i=.Machine$sizeof.long, | |
276 I=.Machine$sizeof.long, | |
277 j=.Machine$sizeof.long, | |
278 J=.Machine$sizeof.long, | |
279 l=.Machine$sizeof.longlong, | |
280 L=.Machine$sizeof.longlong, | |
281 f=4L, | |
282 d=8L, | |
283 "*"=.Machine$sizeof.pointer, | |
284 p=.Machine$sizeof.pointer, | |
285 x=.Machine$sizeof.pointer, | |
286 Z=.Machine$sizeof.pointer, | |
287 v=0L | |
288 ) | |
289 | |
290 align <- function(start, type) | |
291 { | |
292 start %% sizeof(x) | |
293 } | |
294 | |
295 sizeof <- function(x) | |
296 { | |
297 first <- substr(x,1,1) | |
298 if (first == "<") { | |
299 if ( substr(x, nchar(x), nchar(x) ) != ">" ) stop("invalid signature") | |
300 typeName <- substr(x,2,nchar(x)-2) | |
301 sizeof(getType(typeName)) | |
302 } else { | |
303 .sizeof[[substr(x, 1,1)]] | |
304 } | |
305 } | |
306 | |
307 sizeof.struct <- function(x) | |
308 { | |
309 total <- 0L | |
310 for(i in x) | |
311 { | |
312 size <- sizeof(i) | |
313 total <- total + total %% size + size | |
314 } | |
315 return(total) | |
316 } | |
317 | |
318 | |
319 sizeof(struct("iii")) | |
320 sizeof(union("iii")) | |
321 |