@@ -15,6 +15,7 @@ data Option
15
15
= PrintFeature
16
16
| PrintTokens
17
17
| PrintFunctions
18
+ | PrintExtensions
18
19
| UseApi API
19
20
| UseVersion Version
20
21
| UseProfile ProfileName
@@ -25,6 +26,7 @@ options =
25
26
[ G. Option [' F' ] [" print-feature" ] (G. NoArg PrintFeature ) " print feature"
26
27
, G. Option [' t' ] [" print-tokens" ] (G. NoArg PrintTokens ) " print tokens"
27
28
, G. Option [' f' ] [" print-functions" ] (G. NoArg PrintFunctions ) " print functions"
29
+ , G. Option [' x' ] [" print-extensions" ] (G. NoArg PrintExtensions ) " print extensions"
28
30
, G. Option [' a' ] [" api" ] (G. ReqArg (UseApi . API ) " API" ) " extract features for API (default: gl)"
29
31
, G. Option [' v' ] [" version" ] (G. ReqArg (UseVersion . read ) " VERSION" ) " extract features for version (default: 4.5)"
30
32
, G. Option [' p' ] [" profile" ] (G. ReqArg (UseProfile . ProfileName ) " PROFILE" ) " extract features for profile (default: compatibility)" ]
@@ -53,37 +55,8 @@ main = do
53
55
let modName = " Graphics.Rendering.OpenGL.Raw." ++
54
56
capitalize (unProfileName profile) ++
55
57
show (major version) ++ show (minor version)
56
- putStrLn " --------------------------------------------------------------------------------"
57
- putStrLn " -- |"
58
- putStrLn $ " -- Module : " ++ modName
59
- putStrLn " -- Copyright : (c) Sven Panne 2015"
60
- putStrLn " -- License : BSD3"
61
- putStrLn " --"
62
- putStrLn " -- Maintainer : Sven Panne <[email protected] >"
63
- putStrLn " -- Stability : stable"
64
- putStrLn " -- Portability : portable"
65
- putStrLn " --"
66
- putStrLn " --------------------------------------------------------------------------------"
67
- putStrLn " "
68
- let (ts,es,cs) = fixedGetTyEnCo api version profile registry
69
- putStrLn $ " module " ++ modName ++ " ("
70
- CM. unless (null ts) $ do
71
- putStrLn " -- * Types"
72
- putStr $ separate unTypeName ts
73
- putStrLn $ if null es && null cs then " " else " ,"
74
- CM. unless (null es) $ do
75
- putStrLn " -- * Enums"
76
- putStr $ separate (unEnumName . enumName) es
77
- putStrLn $ if null cs then " " else " ,"
78
- CM. unless (null cs) $ do
79
- putStrLn " -- * Functions"
80
- putStr $ separate (unCommandName . commandName) cs
81
- putStrLn " "
82
- putStrLn " ) where"
83
- putStrLn " "
84
- putStrLn " import Graphics.Rendering.OpenGL.Raw.Types"
85
- putStrLn " import Graphics.Rendering.OpenGL.Raw.Tokens"
86
- putStrLn " import Graphics.Rendering.OpenGL.Raw.Functions"
58
+ (ts,es,cs) = fixedReplay api version profile registry
59
+ printMod modName ts es cs
87
60
CM. when (PrintTokens `elem` opts) $ do
88
61
putStrLn " --------------------------------------------------------------------------------"
89
62
putStrLn " -- |"
@@ -146,48 +119,175 @@ main = do
146
119
putStrLn " throwIfNullFunPtr = throwIf (== nullFunPtr) . const"
147
120
putStrLn " "
148
121
mapM_ (putStrLn . showCommand api) (M. elems (commands registry))
122
+ CM. when (PrintExtensions `elem` opts) $ do
123
+ -- only consider non-empty supported extensions/modifications for the given API
124
+ let supportedExtensions =
125
+ [ nameAndMods
126
+ | ext <- extensions registry
127
+ , api `supports` extensionSupported ext
128
+ , nameAndMods@ (_,(_: _)) <- [nameAndModifications api ext] ]
129
+
130
+ let (profileDependent, profileIndependent) =
131
+ L. partition (any (DM. isJust . modificationProfile) . snd ) supportedExtensions
132
+ putStrLn " ======================================== profile-dependent extensions"
133
+ CM. forM_ [" core" , " compatibility" ] $ \ prof -> do
134
+ CM. forM_ profileDependent $ \ (n,mods) -> do
135
+ let (_vendor, modName) = mangleExtensionName (extendExtensionName n (ProfileName prof))
136
+ (ts,es,cs) = executeModifications api (ProfileName prof) registry mods
137
+ printMod modName ts es cs
138
+
139
+ putStrLn " ======================================== profile-independent extensions"
140
+ CM. forM_ profileIndependent $ \ (n,mods) -> do
141
+ let (_vendor, modName) = mangleExtensionName n
142
+ (ts,es,cs) = executeModifications api profile registry mods
143
+ printMod modName ts es cs
144
+
145
+ extendExtensionName :: ExtensionName -> ProfileName -> ExtensionName
146
+ extendExtensionName n profile =
147
+ ExtensionName . (++ (" _" ++ unProfileName profile)). unExtensionName $ n
148
+
149
+ mangleExtensionName :: ExtensionName -> (String ,String )
150
+ mangleExtensionName n = (vendor, modName)
151
+ where (" GL" : vendor: rest) = splitBy (== ' _' ) (unExtensionName n)
152
+ modName = " Graphics.Rendering.OpenGL.Raw." ++ fixVendor vendor ++ " ." ++ concatMap fixExtensionWord rest
153
+
154
+ fixVendor :: String -> String
155
+ fixVendor v = case v of
156
+ " 3DFX" -> " ThreeDFX"
157
+ _ -> v
158
+
159
+ fixExtensionWord :: String -> String
160
+ fixExtensionWord w = case w of
161
+ " 422" -> " FourTwoTwo" -- !!!!!!!!!!!!!!!!!!!
162
+ " 64bit" -> " 64Bit"
163
+ " ES2" -> " ES2"
164
+ " ES3" -> " ES3"
165
+ " FXT1" -> " FXT1"
166
+ " a2ui" -> " A2UI"
167
+ " abgr" -> " ABGR"
168
+ " astc" -> " ASTC"
169
+ " bgra" -> " BGRA"
170
+ " bptc" -> " BPTC"
171
+ " cl" -> " CL"
172
+ " cmyka" -> " CMYKA"
173
+ " dxt1" -> " DXT1"
174
+ " es" -> " ES"
175
+ " fp64" -> " FP64"
176
+ " gpu" -> " GPU"
177
+ " hdr" -> " HDR"
178
+ " latc" -> " LATC"
179
+ " ldr" -> " LDR"
180
+ " lod" -> " LOD"
181
+ " pn" -> " PN"
182
+ " rg" -> " RG"
183
+ " rgb" -> " RGB"
184
+ " rgb10" -> " RGB10"
185
+ " rgtc" -> " RGTC"
186
+ " s3tc" -> " S3TC"
187
+ " sRGB" -> " SRGB"
188
+ " snorm" -> " SNorm"
189
+ " tbuffer" -> " TBuffer"
190
+ " texture3D" -> " Texture3D"
191
+ " texture4D" -> " Texture4D"
192
+ " vdpau" -> " VDPAU"
193
+ " ycbcr" -> " YCbCr"
194
+ " ycrcb" -> " YCrCb"
195
+ " ycrcba" -> " YCrCbA"
196
+ _ -> capitalize w
197
+
198
+ nameAndModifications :: API -> Extension -> (ExtensionName , [Modification ])
199
+ nameAndModifications api e =
200
+ (extensionName e,
201
+ [ conditionalModificationModification cm
202
+ | cm <- extensionsRequireRemove e
203
+ , api `matches` conditionalModificationAPI cm ])
204
+
205
+ supports :: API -> Maybe [API ] -> Bool
206
+ _ `supports` Nothing = True
207
+ a `supports` Just apis = a `elem` apis
149
208
150
209
capitalize :: String -> String
151
- capitalize str = C. toUpper (head str) : tail str
210
+ capitalize str = C. toUpper (head str) : map C. toLower ( tail str)
152
211
153
212
separate :: (a -> String ) -> [a ] -> String
154
213
separate f = L. intercalate " ,\n " . map (" " ++ ) . map f
155
214
215
+ printMod :: String -> [TypeName ] -> [Enum' ] -> [Command ] -> IO ()
216
+ printMod modName ts es cs= do
217
+ putStrLn " --------------------------------------------------------------------------------"
218
+ putStrLn " -- |"
219
+ putStrLn $ " -- Module : " ++ modName
220
+ putStrLn " -- Copyright : (c) Sven Panne 2015"
221
+ putStrLn " -- License : BSD3"
222
+ putStrLn " --"
223
+ putStrLn " -- Maintainer : Sven Panne <[email protected] >"
224
+ putStrLn " -- Stability : stable"
225
+ putStrLn " -- Portability : portable"
226
+ putStrLn " --"
227
+ putStrLn " --------------------------------------------------------------------------------"
228
+ putStrLn " "
229
+ putStrLn $ " module " ++ modName ++ " ("
230
+ CM. unless (null ts) $ do
231
+ putStrLn " -- * Types"
232
+ putStr $ separate unTypeName ts
233
+ putStrLn $ if null es && null cs then " " else " ,"
234
+ CM. unless (null es) $ do
235
+ putStrLn " -- * Enums"
236
+ putStr $ separate (unEnumName . enumName) es
237
+ putStrLn $ if null cs then " " else " ,"
238
+ CM. unless (null cs) $ do
239
+ putStrLn " -- * Functions"
240
+ putStr $ separate (unCommandName . commandName) cs
241
+ putStrLn " "
242
+ putStrLn " ) where"
243
+ putStrLn " "
244
+ CM. unless (null ts) $
245
+ putStrLn " import Graphics.Rendering.OpenGL.Raw.Types"
246
+ CM. unless (null es) $
247
+ putStrLn " import Graphics.Rendering.OpenGL.Raw.Tokens"
248
+ CM. unless (null cs) $
249
+ putStrLn " import Graphics.Rendering.OpenGL.Raw.Functions"
250
+
156
251
-- Annoyingly enough, the OpenGL registry doesn't contain any enums for
157
- -- OpenGL 1.0, so let's just use the OpenGL 1.1 ones.
158
- fixedGetTyEnCo :: API -> Version -> ProfileName -> Registry -> ([TypeName ],[Enum' ],[Command ])
159
- fixedGetTyEnCo api version profile registry
160
- | api == API " gl" && version == read " 1.0" = (ts, es11, cs)
161
- | otherwise = tec
162
- where tec@ (ts, _, cs) = getTyEnCo api version profile registry
163
- (_, es11, _) = getTyEnCo api (read " 1.1" ) profile registry
164
-
165
- getTyEnCo :: API -> Version -> ProfileName -> Registry -> ([TypeName ],[Enum' ],[Command ])
166
- getTyEnCo api version profile registry = (ts', es, cs)
252
+ -- OpenGL 1.0, so let's just use the OpenGL 1.1 ones. Furthermore, features
253
+ -- don't explicitly list the types referenced by commands, so we add them.
254
+ fixedReplay :: API -> Version -> ProfileName -> Registry -> ([TypeName ],[Enum' ],[Command ])
255
+ fixedReplay api version profile registry
256
+ | api == API " gl" && version == read " 1.0" = (ts', es11, cs)
257
+ | otherwise = (ts', es, cs)
258
+ where (ts, es, cs) = replay api version profile registry
259
+ (_, es11, _) = replay api (read " 1.1" ) profile registry
260
+ ts' = S. toList . S. unions $ S. fromList ts : map referencedTypes cs
261
+
262
+ -- Here is the heart of the feature construction logic: Chronologically replay
263
+ -- the whole version history for the given API/version/profile triple.
264
+ replay :: API -> Version -> ProfileName -> Registry -> ([TypeName ],[Enum' ],[Command ])
265
+ replay api version profile registry =
266
+ executeModifications api profile registry modifications
267
+ where modifications = concatMap modificationsFor history
268
+ modificationsFor = flip lookup' (features registry)
269
+ history = L. sort [ key
270
+ | key@ (a,v) <- M. keys (features registry)
271
+ , a == api
272
+ , v <= version ]
273
+
274
+ executeModifications :: API -> ProfileName -> Registry -> [Modification ] -> ([TypeName ], [Enum' ], [Command ])
275
+ executeModifications api profile registry modifications = (ts, es, cs)
167
276
where ts = [ n | TypeElement n <- lst ]
168
277
es = [ e | EnumElement n <- lst
169
278
, e <- lookup' n (enums registry)
170
279
, api `matches` enumAPI e ]
171
280
cs = [ lookup' n (commands registry) | CommandElement n <- lst ]
172
- -- Features don't explicitly list the types referenced by commands.
173
- ts' = S. toList . S. unions $ S. fromList ts : map referencedTypes cs
174
- lst = S. toList $ interfaceElementsFor api version profile registry
281
+ lst = S. toList $ interfaceElementsFor profile modifications
175
282
176
- -- Here is the heart of the feature construction logic: Chronologically replay
177
- -- the whole version history for the given API/version/profile triple.
178
- interfaceElementsFor :: API -> Version -> ProfileName -> Registry -> S. Set InterfaceElement
179
- interfaceElementsFor api version profile registry =
283
+ interfaceElementsFor :: ProfileName -> [Modification ] -> S. Set InterfaceElement
284
+ interfaceElementsFor profile modifications =
180
285
foldl (flip ($) ) S. empty modificationsFor
181
286
where modificationsFor =
182
287
[ op (modificationKind m) ie
183
- | key <- L. sort keys
184
- , m <- lookup' key (features registry)
288
+ | m <- modifications
185
289
, profile `matches` modificationProfile m
186
290
, ie <- modificationInterfaceElements m ]
187
- keys = [ key
188
- | key@ (a,v) <- M. keys (features registry)
189
- , a == api
190
- , v <= version ]
191
291
op Require = S. insert
192
292
op Remove = S. delete
193
293
0 commit comments