Skip to content

Commit

Permalink
Use pattern synonyms.
Browse files Browse the repository at this point in the history
  • Loading branch information
svenpanne committed Dec 30, 2015
1 parent 4592045 commit f2596ae
Show file tree
Hide file tree
Showing 457 changed files with 47,645 additions and 47,195 deletions.
4 changes: 3 additions & 1 deletion OpenGLRaw.cabal
Expand Up @@ -610,7 +610,9 @@ library
transformers >= 0.2 && < 0.6
default-language: Haskell2010
ghc-options: -Wall
other-extensions: CPP
other-extensions:
CPP
PatternSynonyms
if os(windows) && flag(UseNativeWindowsLibraries)
if arch(i386)
cpp-options: "-DCALLCONV=stdcall"
Expand Down
13 changes: 7 additions & 6 deletions RegistryProcessor/src/Main.hs
Expand Up @@ -77,7 +77,7 @@ printTokens api registry = do
let comment =
["All enumeration tokens from the",
"<http://www.opengl.org/registry/ OpenGL registry>."]
startModule ["Tokens"] Nothing comment $ \moduleName h -> do
startModule ["Tokens"] (Just "{-# LANGUAGE PatternSynonyms #-}") comment $ \moduleName h -> do
SI.hPutStrLn h $ "module " ++ moduleName ++ " where"
SI.hPutStrLn h ""
SI.hPutStrLn h $ "import " ++ moduleNameFor ["Types"]
Expand Down Expand Up @@ -369,8 +369,9 @@ separate f = L.intercalate ",\n" . map (" " ++) . map f

-- Note that we handle features just like extensions.
printExtension :: [String] -> Maybe ExtensionName -> ExtensionParts -> IO ()
printExtension moduleNameSuffix mbExtName (ts, es, cs) =
startModule moduleNameSuffix Nothing [] $ \moduleName h -> do
printExtension moduleNameSuffix mbExtName (ts, es, cs) = do
let pragma = if null es then Nothing else Just "{-# LANGUAGE PatternSynonyms #-}"
startModule moduleNameSuffix pragma [] $ \moduleName h -> do
SI.hPutStrLn h $ "module "++ moduleName ++ " ("
flip (maybe (return ())) mbExtName $ \extName -> do
SI.hPutStrLn h " -- * Extension Support"
Expand All @@ -382,7 +383,7 @@ printExtension moduleNameSuffix mbExtName (ts, es, cs) =
SI.hPutStrLn h $ if null es && null cs then "" else ","
CM.unless (null es) $ do
SI.hPutStrLn h " -- * Enums"
SI.hPutStr h $ separate (unEnumName . enumName) es
SI.hPutStr h $ separate (("pattern " ++) . unEnumName . enumName) es
SI.hPutStrLn h $ if null cs then "" else ","
CM.unless (null cs) $ do
SI.hPutStrLn h " -- * Functions"
Expand Down Expand Up @@ -545,8 +546,8 @@ s `matches` Just t = s == t

convertEnum :: Enum' -> [String]
convertEnum e =
[ n ++ " :: " ++ unTypeName (enumType e)
, n ++ " = " ++ unEnumValue (enumValue e) ]
[ "pattern " ++ n ++ " :: " ++ unTypeName (enumType e)
, "pattern " ++ n ++ " = " ++ unEnumValue (enumValue e) ]
where n = unEnumName . enumName $ e

showCommand :: API -> Registry -> M.Map String String -> Command -> String
Expand Down
11 changes: 3 additions & 8 deletions RegistryProcessor/src/MangledRegistry.hs
Expand Up @@ -108,7 +108,7 @@ data Group = Group {

toGroup :: R.Group -> Group
toGroup g = Group {
groupEnums = map (mangleEnumName . R.unName) (R.groupEnums g) }
groupEnums = map (EnumName . R.unName) (R.groupEnums g) }

-- NOTE: Due to an oversight in the OpenGL ES spec, an enum can have different
-- values for different APIs (happens only for GL_ACTIVE_PROGRAM_EXT).
Expand All @@ -124,12 +124,7 @@ toEnum' toTypeName e = Enum {
enumValue = EnumValue (R.enumValue e),
enumAPI = API `fmap` R.enumAPI e,
enumType = toTypeName (R.enumType e),
enumName = mangleEnumName (R.enumName e) }

mangleEnumName :: String -> EnumName
mangleEnumName =
EnumName . joinWords . headToLower . splitWords
where headToLower xs = map C.toLower (head xs) : tail xs
enumName = EnumName (R.enumName e) }

splitChar :: Char
splitChar = '_'
Expand Down Expand Up @@ -267,7 +262,7 @@ toInterfaceElement :: R.InterfaceElement -> InterfaceElement
toInterfaceElement i =
(case R.interfaceElementKind i of
R.InterfaceElementType -> TypeElement . R.TypeName
R.InterfaceElementEnum -> EnumElement . mangleEnumName
R.InterfaceElementEnum -> EnumElement . EnumName
R.InterfaceElementCommand -> CommandElement . CommandName)
(R.unName (R.interfaceElementName i))

Expand Down
5 changes: 3 additions & 2 deletions src/Graphics/GL/AMD/BlendMinmaxFactor.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.BlendMinmaxFactor
Expand All @@ -15,8 +16,8 @@ module Graphics.GL.AMD.BlendMinmaxFactor (
glGetAMDBlendMinmaxFactor,
gl_AMD_blend_minmax_factor,
-- * Enums
gl_FACTOR_MAX_AMD,
gl_FACTOR_MIN_AMD
pattern GL_FACTOR_MAX_AMD,
pattern GL_FACTOR_MIN_AMD
) where

import Graphics.GL.ExtensionPredicates
Expand Down
29 changes: 15 additions & 14 deletions src/Graphics/GL/AMD/DebugOutput.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.DebugOutput
Expand All @@ -15,20 +16,20 @@ module Graphics.GL.AMD.DebugOutput (
glGetAMDDebugOutput,
gl_AMD_debug_output,
-- * Enums
gl_DEBUG_CATEGORY_API_ERROR_AMD,
gl_DEBUG_CATEGORY_APPLICATION_AMD,
gl_DEBUG_CATEGORY_DEPRECATION_AMD,
gl_DEBUG_CATEGORY_OTHER_AMD,
gl_DEBUG_CATEGORY_PERFORMANCE_AMD,
gl_DEBUG_CATEGORY_SHADER_COMPILER_AMD,
gl_DEBUG_CATEGORY_UNDEFINED_BEHAVIOR_AMD,
gl_DEBUG_CATEGORY_WINDOW_SYSTEM_AMD,
gl_DEBUG_LOGGED_MESSAGES_AMD,
gl_DEBUG_SEVERITY_HIGH_AMD,
gl_DEBUG_SEVERITY_LOW_AMD,
gl_DEBUG_SEVERITY_MEDIUM_AMD,
gl_MAX_DEBUG_LOGGED_MESSAGES_AMD,
gl_MAX_DEBUG_MESSAGE_LENGTH_AMD,
pattern GL_DEBUG_CATEGORY_API_ERROR_AMD,
pattern GL_DEBUG_CATEGORY_APPLICATION_AMD,
pattern GL_DEBUG_CATEGORY_DEPRECATION_AMD,
pattern GL_DEBUG_CATEGORY_OTHER_AMD,
pattern GL_DEBUG_CATEGORY_PERFORMANCE_AMD,
pattern GL_DEBUG_CATEGORY_SHADER_COMPILER_AMD,
pattern GL_DEBUG_CATEGORY_UNDEFINED_BEHAVIOR_AMD,
pattern GL_DEBUG_CATEGORY_WINDOW_SYSTEM_AMD,
pattern GL_DEBUG_LOGGED_MESSAGES_AMD,
pattern GL_DEBUG_SEVERITY_HIGH_AMD,
pattern GL_DEBUG_SEVERITY_LOW_AMD,
pattern GL_DEBUG_SEVERITY_MEDIUM_AMD,
pattern GL_MAX_DEBUG_LOGGED_MESSAGES_AMD,
pattern GL_MAX_DEBUG_MESSAGE_LENGTH_AMD,
-- * Functions
glDebugMessageCallbackAMD,
glDebugMessageEnableAMD,
Expand Down
5 changes: 3 additions & 2 deletions src/Graphics/GL/AMD/DepthClampSeparate.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.DepthClampSeparate
Expand All @@ -15,8 +16,8 @@ module Graphics.GL.AMD.DepthClampSeparate (
glGetAMDDepthClampSeparate,
gl_AMD_depth_clamp_separate,
-- * Enums
gl_DEPTH_CLAMP_FAR_AMD,
gl_DEPTH_CLAMP_NEAR_AMD
pattern GL_DEPTH_CLAMP_FAR_AMD,
pattern GL_DEPTH_CLAMP_NEAR_AMD
) where

import Graphics.GL.ExtensionPredicates
Expand Down
57 changes: 29 additions & 28 deletions src/Graphics/GL/AMD/GPUShaderInt64.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.GPUShaderInt64
Expand All @@ -15,34 +16,34 @@ module Graphics.GL.AMD.GPUShaderInt64 (
glGetAMDGPUShaderInt64,
gl_AMD_gpu_shader_int64,
-- * Enums
gl_FLOAT16_NV,
gl_FLOAT16_VEC2_NV,
gl_FLOAT16_VEC3_NV,
gl_FLOAT16_VEC4_NV,
gl_INT16_NV,
gl_INT16_VEC2_NV,
gl_INT16_VEC3_NV,
gl_INT16_VEC4_NV,
gl_INT64_NV,
gl_INT64_VEC2_NV,
gl_INT64_VEC3_NV,
gl_INT64_VEC4_NV,
gl_INT8_NV,
gl_INT8_VEC2_NV,
gl_INT8_VEC3_NV,
gl_INT8_VEC4_NV,
gl_UNSIGNED_INT16_NV,
gl_UNSIGNED_INT16_VEC2_NV,
gl_UNSIGNED_INT16_VEC3_NV,
gl_UNSIGNED_INT16_VEC4_NV,
gl_UNSIGNED_INT64_NV,
gl_UNSIGNED_INT64_VEC2_NV,
gl_UNSIGNED_INT64_VEC3_NV,
gl_UNSIGNED_INT64_VEC4_NV,
gl_UNSIGNED_INT8_NV,
gl_UNSIGNED_INT8_VEC2_NV,
gl_UNSIGNED_INT8_VEC3_NV,
gl_UNSIGNED_INT8_VEC4_NV,
pattern GL_FLOAT16_NV,
pattern GL_FLOAT16_VEC2_NV,
pattern GL_FLOAT16_VEC3_NV,
pattern GL_FLOAT16_VEC4_NV,
pattern GL_INT16_NV,
pattern GL_INT16_VEC2_NV,
pattern GL_INT16_VEC3_NV,
pattern GL_INT16_VEC4_NV,
pattern GL_INT64_NV,
pattern GL_INT64_VEC2_NV,
pattern GL_INT64_VEC3_NV,
pattern GL_INT64_VEC4_NV,
pattern GL_INT8_NV,
pattern GL_INT8_VEC2_NV,
pattern GL_INT8_VEC3_NV,
pattern GL_INT8_VEC4_NV,
pattern GL_UNSIGNED_INT16_NV,
pattern GL_UNSIGNED_INT16_VEC2_NV,
pattern GL_UNSIGNED_INT16_VEC3_NV,
pattern GL_UNSIGNED_INT16_VEC4_NV,
pattern GL_UNSIGNED_INT64_NV,
pattern GL_UNSIGNED_INT64_VEC2_NV,
pattern GL_UNSIGNED_INT64_VEC3_NV,
pattern GL_UNSIGNED_INT64_VEC4_NV,
pattern GL_UNSIGNED_INT8_NV,
pattern GL_UNSIGNED_INT8_VEC2_NV,
pattern GL_UNSIGNED_INT8_VEC3_NV,
pattern GL_UNSIGNED_INT8_VEC4_NV,
-- * Functions
glGetUniformi64vNV,
glGetUniformui64vNV,
Expand Down
19 changes: 10 additions & 9 deletions src/Graphics/GL/AMD/InterleavedElements.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.InterleavedElements
Expand All @@ -15,15 +16,15 @@ module Graphics.GL.AMD.InterleavedElements (
glGetAMDInterleavedElements,
gl_AMD_interleaved_elements,
-- * Enums
gl_ALPHA,
gl_BLUE,
gl_GREEN,
gl_RED,
gl_RG16UI,
gl_RG8UI,
gl_RGBA8UI,
gl_VERTEX_ELEMENT_SWIZZLE_AMD,
gl_VERTEX_ID_SWIZZLE_AMD,
pattern GL_ALPHA,
pattern GL_BLUE,
pattern GL_GREEN,
pattern GL_RED,
pattern GL_RG16UI,
pattern GL_RG8UI,
pattern GL_RGBA8UI,
pattern GL_VERTEX_ELEMENT_SWIZZLE_AMD,
pattern GL_VERTEX_ID_SWIZZLE_AMD,
-- * Functions
glVertexAttribParameteriAMD
) where
Expand Down
11 changes: 6 additions & 5 deletions src/Graphics/GL/AMD/NameGenDelete.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.NameGenDelete
Expand All @@ -15,11 +16,11 @@ module Graphics.GL.AMD.NameGenDelete (
glGetAMDNameGenDelete,
gl_AMD_name_gen_delete,
-- * Enums
gl_DATA_BUFFER_AMD,
gl_PERFORMANCE_MONITOR_AMD,
gl_QUERY_OBJECT_AMD,
gl_SAMPLER_OBJECT_AMD,
gl_VERTEX_ARRAY_OBJECT_AMD,
pattern GL_DATA_BUFFER_AMD,
pattern GL_PERFORMANCE_MONITOR_AMD,
pattern GL_QUERY_OBJECT_AMD,
pattern GL_SAMPLER_OBJECT_AMD,
pattern GL_VERTEX_ARRAY_OBJECT_AMD,
-- * Functions
glDeleteNamesAMD,
glGenNamesAMD,
Expand Down
13 changes: 7 additions & 6 deletions src/Graphics/GL/AMD/OcclusionQueryEvent.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.OcclusionQueryEvent
Expand All @@ -15,12 +16,12 @@ module Graphics.GL.AMD.OcclusionQueryEvent (
glGetAMDOcclusionQueryEvent,
gl_AMD_occlusion_query_event,
-- * Enums
gl_OCCLUSION_QUERY_EVENT_MASK_AMD,
gl_QUERY_ALL_EVENT_BITS_AMD,
gl_QUERY_DEPTH_BOUNDS_FAIL_EVENT_BIT_AMD,
gl_QUERY_DEPTH_FAIL_EVENT_BIT_AMD,
gl_QUERY_DEPTH_PASS_EVENT_BIT_AMD,
gl_QUERY_STENCIL_FAIL_EVENT_BIT_AMD,
pattern GL_OCCLUSION_QUERY_EVENT_MASK_AMD,
pattern GL_QUERY_ALL_EVENT_BITS_AMD,
pattern GL_QUERY_DEPTH_BOUNDS_FAIL_EVENT_BIT_AMD,
pattern GL_QUERY_DEPTH_FAIL_EVENT_BIT_AMD,
pattern GL_QUERY_DEPTH_PASS_EVENT_BIT_AMD,
pattern GL_QUERY_STENCIL_FAIL_EVENT_BIT_AMD,
-- * Functions
glQueryObjectParameteruiAMD
) where
Expand Down
15 changes: 8 additions & 7 deletions src/Graphics/GL/AMD/PerformanceMonitor.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.PerformanceMonitor
Expand All @@ -15,13 +16,13 @@ module Graphics.GL.AMD.PerformanceMonitor (
glGetAMDPerformanceMonitor,
gl_AMD_performance_monitor,
-- * Enums
gl_COUNTER_RANGE_AMD,
gl_COUNTER_TYPE_AMD,
gl_PERCENTAGE_AMD,
gl_PERFMON_RESULT_AMD,
gl_PERFMON_RESULT_AVAILABLE_AMD,
gl_PERFMON_RESULT_SIZE_AMD,
gl_UNSIGNED_INT64_AMD,
pattern GL_COUNTER_RANGE_AMD,
pattern GL_COUNTER_TYPE_AMD,
pattern GL_PERCENTAGE_AMD,
pattern GL_PERFMON_RESULT_AMD,
pattern GL_PERFMON_RESULT_AVAILABLE_AMD,
pattern GL_PERFMON_RESULT_SIZE_AMD,
pattern GL_UNSIGNED_INT64_AMD,
-- * Functions
glBeginPerfMonitorAMD,
glDeletePerfMonitorsAMD,
Expand Down
3 changes: 2 additions & 1 deletion src/Graphics/GL/AMD/PinnedMemory.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.PinnedMemory
Expand All @@ -15,7 +16,7 @@ module Graphics.GL.AMD.PinnedMemory (
glGetAMDPinnedMemory,
gl_AMD_pinned_memory,
-- * Enums
gl_EXTERNAL_VIRTUAL_MEMORY_BUFFER_AMD
pattern GL_EXTERNAL_VIRTUAL_MEMORY_BUFFER_AMD
) where

import Graphics.GL.ExtensionPredicates
Expand Down
7 changes: 4 additions & 3 deletions src/Graphics/GL/AMD/QueryBufferObject.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.QueryBufferObject
Expand All @@ -15,9 +16,9 @@ module Graphics.GL.AMD.QueryBufferObject (
glGetAMDQueryBufferObject,
gl_AMD_query_buffer_object,
-- * Enums
gl_QUERY_BUFFER_AMD,
gl_QUERY_BUFFER_BINDING_AMD,
gl_QUERY_RESULT_NO_WAIT_AMD
pattern GL_QUERY_BUFFER_AMD,
pattern GL_QUERY_BUFFER_BINDING_AMD,
pattern GL_QUERY_RESULT_NO_WAIT_AMD
) where

import Graphics.GL.ExtensionPredicates
Expand Down
3 changes: 2 additions & 1 deletion src/Graphics/GL/AMD/SamplePositions.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.SamplePositions
Expand All @@ -15,7 +16,7 @@ module Graphics.GL.AMD.SamplePositions (
glGetAMDSamplePositions,
gl_AMD_sample_positions,
-- * Enums
gl_SUBSAMPLE_DISTANCE_AMD,
pattern GL_SUBSAMPLE_DISTANCE_AMD,
-- * Functions
glSetMultisamplefvAMD
) where
Expand Down
3 changes: 2 additions & 1 deletion src/Graphics/GL/AMD/SeamlessCubemapPerTexture.hs
@@ -1,3 +1,4 @@
{-# LANGUAGE PatternSynonyms #-}
--------------------------------------------------------------------------------
-- |
-- Module : Graphics.GL.AMD.SeamlessCubemapPerTexture
Expand All @@ -15,7 +16,7 @@ module Graphics.GL.AMD.SeamlessCubemapPerTexture (
glGetAMDSeamlessCubemapPerTexture,
gl_AMD_seamless_cubemap_per_texture,
-- * Enums
gl_TEXTURE_CUBE_MAP_SEAMLESS
pattern GL_TEXTURE_CUBE_MAP_SEAMLESS
) where

import Graphics.GL.ExtensionPredicates
Expand Down

0 comments on commit f2596ae

Please sign in to comment.