{-# LANGUAGE OverloadedStrings #-} module Skylighting.Syntax.Gcc (syntax) where import Skylighting.Types import Data.Map import Skylighting.Regex import qualified Data.Set syntax :: Syntax syntax = Syntax { sName = "GCCExtensions" , sFilename = "gcc.xml" , sShortname = "Gcc" , sContexts = fromList [ ( "AttrArgs" , Context { cName = "AttrArgs" , cSyntax = "GCCExtensions" , cRules = [ Rule { rMatcher = Detect2Chars '(' '(' , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Detect2Chars ')' ')' , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '(' , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "GCCExtensions" , "Close" ) ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [ Pop ] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "AttrStringArg" , Context { cName = "AttrStringArg" , cSyntax = "GCCExtensions" , cRules = [ Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } ] , cAttribute = StringTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "Close" , Context { cName = "Close" , cSyntax = "GCCExtensions" , cRules = [ Rule { rMatcher = DetectChar ')' , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Pop ] } , Rule { rMatcher = DetectChar '"' , rAttribute = StringTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "GCCExtensions" , "AttrStringArg" ) ] } ] , cAttribute = ExtensionTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "DetectGccExtensions" , Context { cName = "DetectGccExtensions" , cSyntax = "GCCExtensions" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "_FORTIFY_SOURCE" , "_GNU_SOURCE" , "_ILP32" , "_LP64" , "_REENTRANT" , "_STDC_PREDEF_H" , "__3dNOW_A__" , "__3dNOW__" , "__ABM__" , "__ADX__" , "__AES__" , "__ATOMIC_ACQUIRE" , "__ATOMIC_ACQ_REL" , "__ATOMIC_CONSUME" , "__ATOMIC_HLE_ACQUIRE" , "__ATOMIC_HLE_RELEASE" , "__ATOMIC_RELAXED" , "__ATOMIC_RELEASE" , "__ATOMIC_SEQ_CST" , "__AVX2__" , "__AVX__" , "__BASE_FILE__" , "__BIGGEST_ALIGNMENT__" , "__BMI2__" , "__BMI__" , "__BYTE_ORDER__" , "__CHAR16_TYPE__" , "__CHAR32_TYPE__" , "__CHAR_BIT__" , "__CHAR_UNSIGNED__" , "__COUNTER__" , "__DBL_DECIMAL_DIG__" , "__DBL_DENORM_MIN__" , "__DBL_DIG__" , "__DBL_EPSILON__" , "__DBL_HAS_DENORM__" , "__DBL_HAS_INFINITY__" , "__DBL_HAS_QUIET_NAN__" , "__DBL_MANT_DIG__" , "__DBL_MAX_10_EXP__" , "__DBL_MAX_EXP__" , "__DBL_MAX__" , "__DBL_MIN_10_EXP__" , "__DBL_MIN_EXP__" , "__DBL_MIN__" , "__DEC128_EPSILON__" , "__DEC128_MANT_DIG__" , "__DEC128_MAX_EXP__" , "__DEC128_MAX__" , "__DEC128_MIN_EXP__" , "__DEC128_MIN__" , "__DEC128_SUBNORMAL_MIN__" , "__DEC32_EPSILON__" , "__DEC32_MANT_DIG__" , "__DEC32_MAX_EXP__" , "__DEC32_MAX__" , "__DEC32_MIN_EXP__" , "__DEC32_MIN__" , "__DEC32_SUBNORMAL_MIN__" , "__DEC64_EPSILON__" , "__DEC64_MANT_DIG__" , "__DEC64_MAX_EXP__" , "__DEC64_MAX__" , "__DEC64_MIN_EXP__" , "__DEC64_MIN__" , "__DEC64_SUBNORMAL_MIN__" , "__DECIMAL_BID_FORMAT__" , "__DECIMAL_DIG__" , "__DEC_EVAL_METHOD__" , "__DEPRECATED" , "__ELF__" , "__EXCEPTIONS" , "__F16C__" , "__FAST_MATH__" , "__FINITE_MATH_ONLY__" , "__FLOAT_WORD_ORDER__" , "__FLT_DECIMAL_DIG__" , "__FLT_DENORM_MIN__" , "__FLT_DIG__" , "__FLT_EPSILON__" , "__FLT_EVAL_METHOD__" , "__FLT_HAS_DENORM__" , "__FLT_HAS_INFINITY__" , "__FLT_HAS_QUIET_NAN__" , "__FLT_MANT_DIG__" , "__FLT_MAX_10_EXP__" , "__FLT_MAX_EXP__" , "__FLT_MAX__" , "__FLT_MIN_10_EXP__" , "__FLT_MIN_EXP__" , "__FLT_MIN__" , "__FLT_RADIX__" , "__FMA4__" , "__FMA__" , "__FP_FAST_FMA" , "__FP_FAST_FMAF" , "__FSGSBASE__" , "__FUNCTION__" , "__FXSR__" , "__GCC_ATOMIC_BOOL_LOCK_FREE" , "__GCC_ATOMIC_CHAR16_T_LOCK_FREE" , "__GCC_ATOMIC_CHAR32_T_LOCK_FREE" , "__GCC_ATOMIC_CHAR_LOCK_FREE" , "__GCC_ATOMIC_INT_LOCK_FREE" , "__GCC_ATOMIC_LLONG_LOCK_FREE" , "__GCC_ATOMIC_LONG_LOCK_FREE" , "__GCC_ATOMIC_POINTER_LOCK_FREE" , "__GCC_ATOMIC_SHORT_LOCK_FREE" , "__GCC_ATOMIC_TEST_AND_SET_TRUEVAL" , "__GCC_ATOMIC_WCHAR_T_LOCK_FREE" , "__GCC_HAVE_DWARF2_CFI_ASM" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_1" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_16" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_2" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_4" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_8" , "__GFORTRAN__" , "__GNUC_GNU_INLINE__" , "__GNUC_MINOR__" , "__GNUC_PATCHLEVEL__" , "__GNUC_STDC_INLINE__" , "__GNUC__" , "__GNUG__" , "__GXX_ABI_VERSION" , "__GXX_EXPERIMENTAL_CXX0X__" , "__GXX_RTTI" , "__GXX_WEAK__" , "__ILP32__" , "__INCLUDE_LEVEL__" , "__INT16_C" , "__INT16_MAX__" , "__INT16_TYPE__" , "__INT32_C" , "__INT32_MAX__" , "__INT32_TYPE__" , "__INT64_C" , "__INT64_MAX__" , "__INT64_TYPE__" , "__INT8_C" , "__INT8_MAX__" , "__INT8_TYPE__" , "__INTMAX_C" , "__INTMAX_MAX__" , "__INTMAX_TYPE__" , "__INTPTR_MAX__" , "__INTPTR_TYPE__" , "__INT_FAST16_MAX__" , "__INT_FAST16_TYPE__" , "__INT_FAST32_MAX__" , "__INT_FAST32_TYPE__" , "__INT_FAST64_MAX__" , "__INT_FAST64_TYPE__" , "__INT_FAST8_MAX__" , "__INT_FAST8_TYPE__" , "__INT_LEAST16_MAX__" , "__INT_LEAST16_TYPE__" , "__INT_LEAST32_MAX__" , "__INT_LEAST32_TYPE__" , "__INT_LEAST64_MAX__" , "__INT_LEAST64_TYPE__" , "__INT_LEAST8_MAX__" , "__INT_LEAST8_TYPE__" , "__INT_MAX__" , "__LDBL_DENORM_MIN__" , "__LDBL_DIG__" , "__LDBL_EPSILON__" , "__LDBL_HAS_DENORM__" , "__LDBL_HAS_INFINITY__" , "__LDBL_HAS_QUIET_NAN__" , "__LDBL_MANT_DIG__" , "__LDBL_MAX_10_EXP__" , "__LDBL_MAX_EXP__" , "__LDBL_MAX__" , "__LDBL_MIN_10_EXP__" , "__LDBL_MIN_EXP__" , "__LDBL_MIN__" , "__LONG_LONG_MAX__" , "__LONG_MAX__" , "__LP64__" , "__LWP__" , "__LZCNT__" , "__MMX__" , "__NEXT_RUNTIME__" , "__NO_INLINE__" , "__OPTIMIZE_SIZE__" , "__OPTIMIZE__" , "__ORDER_BIG_ENDIAN__" , "__ORDER_LITTLE_ENDIAN__" , "__ORDER_PDP_ENDIAN__" , "__PCLMUL__" , "__PIC__" , "__PIE__" , "__POPCNT__" , "__PRAGMA_REDEFINE_EXTNAME" , "__PRETTY_FUNCTION__" , "__PRFCHW__" , "__PTRDIFF_MAX__" , "__PTRDIFF_TYPE__" , "__RDRND__" , "__RDSEED__" , "__REGISTER_PREFIX__" , "__RTM__" , "__SANITIZE_ADDRESS__" , "__SCHAR_MAX__" , "__SHRT_MAX__" , "__SIG_ATOMIC_MAX__" , "__SIG_ATOMIC_MIN__" , "__SIG_ATOMIC_TYPE__" , "__SIZEOF_DOUBLE__" , "__SIZEOF_FLOAT__" , "__SIZEOF_INT128__" , "__SIZEOF_INT__" , "__SIZEOF_LONG_DOUBLE__" , "__SIZEOF_LONG_LONG__" , "__SIZEOF_LONG__" , "__SIZEOF_POINTER__" , "__SIZEOF_PTRDIFF_T__" , "__SIZEOF_SHORT__" , "__SIZEOF_SIZE_T__" , "__SIZEOF_WCHAR_T__" , "__SIZEOF_WINT_T__" , "__SIZE_MAX__" , "__SIZE_TYPE__" , "__SSE2_MATH__" , "__SSE2__" , "__SSE3__" , "__SSE4A__" , "__SSE4_1__" , "__SSE4_2__" , "__SSE_MATH__" , "__SSE__" , "__SSP_ALL__" , "__SSP__" , "__SSSE3__" , "__STDC_HOSTED__" , "__STDC_IEC_559_COMPLEX__" , "__STDC_IEC_559__" , "__STDC_ISO_10646__" , "__STDC_NO_THREADS__" , "__STDC_UTF_16__" , "__STDC_UTF_32__" , "__STDC_VERSION__" , "__STDC__" , "__STRICT_ANSI__" , "__TBM__" , "__TIMESTAMP__" , "__UINT16_C" , "__UINT16_MAX__" , "__UINT16_TYPE__" , "__UINT32_C" , "__UINT32_MAX__" , "__UINT32_TYPE__" , "__UINT64_C" , "__UINT64_MAX__" , "__UINT64_TYPE__" , "__UINT8_C" , "__UINT8_MAX__" , "__UINT8_TYPE__" , "__UINTMAX_C" , "__UINTMAX_MAX__" , "__UINTMAX_TYPE__" , "__UINTPTR_MAX__" , "__UINTPTR_TYPE__" , "__UINT_FAST16_MAX__" , "__UINT_FAST16_TYPE__" , "__UINT_FAST32_MAX__" , "__UINT_FAST32_TYPE__" , "__UINT_FAST64_MAX__" , "__UINT_FAST64_TYPE__" , "__UINT_FAST8_MAX__" , "__UINT_FAST8_TYPE__" , "__UINT_LEAST16_MAX__" , "__UINT_LEAST16_TYPE__" , "__UINT_LEAST32_MAX__" , "__UINT_LEAST32_TYPE__" , "__UINT_LEAST64_MAX__" , "__UINT_LEAST64_TYPE__" , "__UINT_LEAST8_MAX__" , "__UINT_LEAST8_TYPE__" , "__USER_LABEL_PREFIX__" , "__USING_SJLJ_EXCEPTIONS__" , "__VA_ARGS__" , "__VERSION__" , "__WCHAR_MAX__" , "__WCHAR_MIN__" , "__WCHAR_TYPE__" , "__WCHAR_UNSIGNED__" , "__WINT_MAX__" , "__WINT_MIN__" , "__WINT_TYPE__" , "__XOP__" , "__XSAVEOPT__" , "__XSAVE__" , "__amd64" , "__amd64__" , "__amdfam10" , "__amdfam10__" , "__athlon" , "__athlon__" , "__athlon_sse__" , "__atom" , "__atom__" , "__bdver1" , "__bdver1__" , "__bdver2" , "__bdver2__" , "__bdver3" , "__bdver3__" , "__btver1" , "__btver1__" , "__btver2" , "__btver2__" , "__code_model_32__" , "__code_model_small__" , "__core2" , "__core2__" , "__core_avx2" , "__core_avx2__" , "__corei7" , "__corei7__" , "__cplusplus" , "__geode" , "__geode__" , "__gnu_linux__" , "__i386" , "__i386__" , "__i486" , "__i486__" , "__i586" , "__i586__" , "__i686" , "__i686__" , "__k6" , "__k6_2__" , "__k6_3__" , "__k6__" , "__k8" , "__k8__" , "__linux" , "__linux__" , "__nocona" , "__nocona__" , "__pentium" , "__pentium4" , "__pentium4__" , "__pentium__" , "__pentium_mmx__" , "__pentiumpro" , "__pentiumpro__" , "__pic__" , "__pie__" , "__tune_amdfam10__" , "__tune_athlon__" , "__tune_athlon_sse__" , "__tune_atom__" , "__tune_bdver1__" , "__tune_bdver2__" , "__tune_bdver3__" , "__tune_btver1__" , "__tune_btver2__" , "__tune_core2__" , "__tune_core_avx2__" , "__tune_corei7__" , "__tune_geode__" , "__tune_i386__" , "__tune_i486__" , "__tune_i586__" , "__tune_i686__" , "__tune_k6_2__" , "__tune_k6_3__" , "__tune_k6__" , "__tune_k8__" , "__tune_nocona__" , "__tune_pentium2__" , "__tune_pentium3__" , "__tune_pentium4__" , "__tune_pentium__" , "__tune_pentium_mmx__" , "__tune_pentiumpro__" , "__unix" , "__unix__" , "__x86_64" , "__x86_64__" , "i386" , "linux" , "unix" ]) , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "__atomic_add_fetch" , "__atomic_always_lock_free" , "__atomic_and_fetch" , "__atomic_clear" , "__atomic_compare_exchange" , "__atomic_compare_exchange_n" , "__atomic_exchange" , "__atomic_exchange_n" , "__atomic_fetch_add" , "__atomic_fetch_and" , "__atomic_fetch_nand" , "__atomic_fetch_or" , "__atomic_fetch_sub" , "__atomic_fetch_xor" , "__atomic_is_lock_free" , "__atomic_load" , "__atomic_load_n" , "__atomic_nand_fetch" , "__atomic_or_fetch" , "__atomic_signal_fence" , "__atomic_store" , "__atomic_store_n" , "__atomic_sub_fetch" , "__atomic_test_and_set" , "__atomic_thread_fence" , "__atomic_xor_fetch" , "__has_nothrow_assign" , "__has_nothrow_constructor" , "__has_nothrow_copy" , "__has_trivial_assign" , "__has_trivial_constructor" , "__has_trivial_copy" , "__has_trivial_destructor" , "__has_virtual_destructor" , "__is_abstract" , "__is_base_of" , "__is_class" , "__is_empty" , "__is_enum" , "__is_pod" , "__is_polymorphic" , "__is_union" , "__sync_add_and_fetch" , "__sync_and_and_fetch" , "__sync_bool_compare_and_swap" , "__sync_fetch_and_add" , "__sync_fetch_and_and" , "__sync_fetch_and_nand" , "__sync_fetch_and_or" , "__sync_fetch_and_sub" , "__sync_fetch_and_xor" , "__sync_lock_release" , "__sync_lock_test_and_set" , "__sync_nand_and_fetch" , "__sync_or_and_fetch" , "__sync_sub_and_fetch" , "__sync_synchronize" , "__sync_val_compare_and_swap" , "__sync_xor_and_fetch" ]) , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "_Accum" , "_Decimal128" , "_Decimal32" , "_Decimal64" , "_Fract" , "_Sat" , "__float128" , "__float80" , "__fp16" , "__int128" ]) , rAttribute = DataTypeTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = StringDetect "__attribute__" , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "GCCExtensions" , "AttrArgs" ) ] } , Rule { rMatcher = StringDetect "__declspec" , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [ Push ( "GCCExtensions" , "AttrArgs" ) ] } , Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "__alignof__" , "__asm__" , "__complex__" , "__const__" , "__extension__" , "__imag__" , "__inline__" , "__label__" , "__real__" , "__restrict" , "__restrict__" , "__thread" , "__typeof__" , "typeof" ]) , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "__builtin_[a-zA-Z0-9_]+" , reCompiled = Just (compileRegex True "__builtin_[a-zA-Z0-9_]+") , reCaseSensitive = True } , rAttribute = FunctionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } , Rule { rMatcher = RegExpr RE { reString = "0[Bb][01]+([Uu][Ll]{0,2}|[Ll]{0,2}[Uu]?|_[_0-9A-Za-z]*)?\\b" , reCompiled = Just (compileRegex True "0[Bb][01]+([Uu][Ll]{0,2}|[Ll]{0,2}[Uu]?|_[_0-9A-Za-z]*)?\\b") , reCaseSensitive = True } , rAttribute = ExtensionTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) , ( "GNUMacros" , Context { cName = "GNUMacros" , cSyntax = "GCCExtensions" , cRules = [ Rule { rMatcher = Keyword KeywordAttr { keywordCaseSensitive = True , keywordDelims = Data.Set.fromList "\t\n !%&()*+,-./:;<=>?[\\]^{|}~" } (makeWordSet True [ "_FORTIFY_SOURCE" , "_GNU_SOURCE" , "_ILP32" , "_LP64" , "_REENTRANT" , "_STDC_PREDEF_H" , "__3dNOW_A__" , "__3dNOW__" , "__ABM__" , "__ADX__" , "__AES__" , "__ATOMIC_ACQUIRE" , "__ATOMIC_ACQ_REL" , "__ATOMIC_CONSUME" , "__ATOMIC_HLE_ACQUIRE" , "__ATOMIC_HLE_RELEASE" , "__ATOMIC_RELAXED" , "__ATOMIC_RELEASE" , "__ATOMIC_SEQ_CST" , "__AVX2__" , "__AVX__" , "__BASE_FILE__" , "__BIGGEST_ALIGNMENT__" , "__BMI2__" , "__BMI__" , "__BYTE_ORDER__" , "__CHAR16_TYPE__" , "__CHAR32_TYPE__" , "__CHAR_BIT__" , "__CHAR_UNSIGNED__" , "__COUNTER__" , "__DBL_DECIMAL_DIG__" , "__DBL_DENORM_MIN__" , "__DBL_DIG__" , "__DBL_EPSILON__" , "__DBL_HAS_DENORM__" , "__DBL_HAS_INFINITY__" , "__DBL_HAS_QUIET_NAN__" , "__DBL_MANT_DIG__" , "__DBL_MAX_10_EXP__" , "__DBL_MAX_EXP__" , "__DBL_MAX__" , "__DBL_MIN_10_EXP__" , "__DBL_MIN_EXP__" , "__DBL_MIN__" , "__DEC128_EPSILON__" , "__DEC128_MANT_DIG__" , "__DEC128_MAX_EXP__" , "__DEC128_MAX__" , "__DEC128_MIN_EXP__" , "__DEC128_MIN__" , "__DEC128_SUBNORMAL_MIN__" , "__DEC32_EPSILON__" , "__DEC32_MANT_DIG__" , "__DEC32_MAX_EXP__" , "__DEC32_MAX__" , "__DEC32_MIN_EXP__" , "__DEC32_MIN__" , "__DEC32_SUBNORMAL_MIN__" , "__DEC64_EPSILON__" , "__DEC64_MANT_DIG__" , "__DEC64_MAX_EXP__" , "__DEC64_MAX__" , "__DEC64_MIN_EXP__" , "__DEC64_MIN__" , "__DEC64_SUBNORMAL_MIN__" , "__DECIMAL_BID_FORMAT__" , "__DECIMAL_DIG__" , "__DEC_EVAL_METHOD__" , "__DEPRECATED" , "__ELF__" , "__EXCEPTIONS" , "__F16C__" , "__FAST_MATH__" , "__FINITE_MATH_ONLY__" , "__FLOAT_WORD_ORDER__" , "__FLT_DECIMAL_DIG__" , "__FLT_DENORM_MIN__" , "__FLT_DIG__" , "__FLT_EPSILON__" , "__FLT_EVAL_METHOD__" , "__FLT_HAS_DENORM__" , "__FLT_HAS_INFINITY__" , "__FLT_HAS_QUIET_NAN__" , "__FLT_MANT_DIG__" , "__FLT_MAX_10_EXP__" , "__FLT_MAX_EXP__" , "__FLT_MAX__" , "__FLT_MIN_10_EXP__" , "__FLT_MIN_EXP__" , "__FLT_MIN__" , "__FLT_RADIX__" , "__FMA4__" , "__FMA__" , "__FP_FAST_FMA" , "__FP_FAST_FMAF" , "__FSGSBASE__" , "__FUNCTION__" , "__FXSR__" , "__GCC_ATOMIC_BOOL_LOCK_FREE" , "__GCC_ATOMIC_CHAR16_T_LOCK_FREE" , "__GCC_ATOMIC_CHAR32_T_LOCK_FREE" , "__GCC_ATOMIC_CHAR_LOCK_FREE" , "__GCC_ATOMIC_INT_LOCK_FREE" , "__GCC_ATOMIC_LLONG_LOCK_FREE" , "__GCC_ATOMIC_LONG_LOCK_FREE" , "__GCC_ATOMIC_POINTER_LOCK_FREE" , "__GCC_ATOMIC_SHORT_LOCK_FREE" , "__GCC_ATOMIC_TEST_AND_SET_TRUEVAL" , "__GCC_ATOMIC_WCHAR_T_LOCK_FREE" , "__GCC_HAVE_DWARF2_CFI_ASM" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_1" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_16" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_2" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_4" , "__GCC_HAVE_SYNC_COMPARE_AND_SWAP_8" , "__GFORTRAN__" , "__GNUC_GNU_INLINE__" , "__GNUC_MINOR__" , "__GNUC_PATCHLEVEL__" , "__GNUC_STDC_INLINE__" , "__GNUC__" , "__GNUG__" , "__GXX_ABI_VERSION" , "__GXX_EXPERIMENTAL_CXX0X__" , "__GXX_RTTI" , "__GXX_WEAK__" , "__ILP32__" , "__INCLUDE_LEVEL__" , "__INT16_C" , "__INT16_MAX__" , "__INT16_TYPE__" , "__INT32_C" , "__INT32_MAX__" , "__INT32_TYPE__" , "__INT64_C" , "__INT64_MAX__" , "__INT64_TYPE__" , "__INT8_C" , "__INT8_MAX__" , "__INT8_TYPE__" , "__INTMAX_C" , "__INTMAX_MAX__" , "__INTMAX_TYPE__" , "__INTPTR_MAX__" , "__INTPTR_TYPE__" , "__INT_FAST16_MAX__" , "__INT_FAST16_TYPE__" , "__INT_FAST32_MAX__" , "__INT_FAST32_TYPE__" , "__INT_FAST64_MAX__" , "__INT_FAST64_TYPE__" , "__INT_FAST8_MAX__" , "__INT_FAST8_TYPE__" , "__INT_LEAST16_MAX__" , "__INT_LEAST16_TYPE__" , "__INT_LEAST32_MAX__" , "__INT_LEAST32_TYPE__" , "__INT_LEAST64_MAX__" , "__INT_LEAST64_TYPE__" , "__INT_LEAST8_MAX__" , "__INT_LEAST8_TYPE__" , "__INT_MAX__" , "__LDBL_DENORM_MIN__" , "__LDBL_DIG__" , "__LDBL_EPSILON__" , "__LDBL_HAS_DENORM__" , "__LDBL_HAS_INFINITY__" , "__LDBL_HAS_QUIET_NAN__" , "__LDBL_MANT_DIG__" , "__LDBL_MAX_10_EXP__" , "__LDBL_MAX_EXP__" , "__LDBL_MAX__" , "__LDBL_MIN_10_EXP__" , "__LDBL_MIN_EXP__" , "__LDBL_MIN__" , "__LONG_LONG_MAX__" , "__LONG_MAX__" , "__LP64__" , "__LWP__" , "__LZCNT__" , "__MMX__" , "__NEXT_RUNTIME__" , "__NO_INLINE__" , "__OPTIMIZE_SIZE__" , "__OPTIMIZE__" , "__ORDER_BIG_ENDIAN__" , "__ORDER_LITTLE_ENDIAN__" , "__ORDER_PDP_ENDIAN__" , "__PCLMUL__" , "__PIC__" , "__PIE__" , "__POPCNT__" , "__PRAGMA_REDEFINE_EXTNAME" , "__PRETTY_FUNCTION__" , "__PRFCHW__" , "__PTRDIFF_MAX__" , "__PTRDIFF_TYPE__" , "__RDRND__" , "__RDSEED__" , "__REGISTER_PREFIX__" , "__RTM__" , "__SANITIZE_ADDRESS__" , "__SCHAR_MAX__" , "__SHRT_MAX__" , "__SIG_ATOMIC_MAX__" , "__SIG_ATOMIC_MIN__" , "__SIG_ATOMIC_TYPE__" , "__SIZEOF_DOUBLE__" , "__SIZEOF_FLOAT__" , "__SIZEOF_INT128__" , "__SIZEOF_INT__" , "__SIZEOF_LONG_DOUBLE__" , "__SIZEOF_LONG_LONG__" , "__SIZEOF_LONG__" , "__SIZEOF_POINTER__" , "__SIZEOF_PTRDIFF_T__" , "__SIZEOF_SHORT__" , "__SIZEOF_SIZE_T__" , "__SIZEOF_WCHAR_T__" , "__SIZEOF_WINT_T__" , "__SIZE_MAX__" , "__SIZE_TYPE__" , "__SSE2_MATH__" , "__SSE2__" , "__SSE3__" , "__SSE4A__" , "__SSE4_1__" , "__SSE4_2__" , "__SSE_MATH__" , "__SSE__" , "__SSP_ALL__" , "__SSP__" , "__SSSE3__" , "__STDC_HOSTED__" , "__STDC_IEC_559_COMPLEX__" , "__STDC_IEC_559__" , "__STDC_ISO_10646__" , "__STDC_NO_THREADS__" , "__STDC_UTF_16__" , "__STDC_UTF_32__" , "__STDC_VERSION__" , "__STDC__" , "__STRICT_ANSI__" , "__TBM__" , "__TIMESTAMP__" , "__UINT16_C" , "__UINT16_MAX__" , "__UINT16_TYPE__" , "__UINT32_C" , "__UINT32_MAX__" , "__UINT32_TYPE__" , "__UINT64_C" , "__UINT64_MAX__" , "__UINT64_TYPE__" , "__UINT8_C" , "__UINT8_MAX__" , "__UINT8_TYPE__" , "__UINTMAX_C" , "__UINTMAX_MAX__" , "__UINTMAX_TYPE__" , "__UINTPTR_MAX__" , "__UINTPTR_TYPE__" , "__UINT_FAST16_MAX__" , "__UINT_FAST16_TYPE__" , "__UINT_FAST32_MAX__" , "__UINT_FAST32_TYPE__" , "__UINT_FAST64_MAX__" , "__UINT_FAST64_TYPE__" , "__UINT_FAST8_MAX__" , "__UINT_FAST8_TYPE__" , "__UINT_LEAST16_MAX__" , "__UINT_LEAST16_TYPE__" , "__UINT_LEAST32_MAX__" , "__UINT_LEAST32_TYPE__" , "__UINT_LEAST64_MAX__" , "__UINT_LEAST64_TYPE__" , "__UINT_LEAST8_MAX__" , "__UINT_LEAST8_TYPE__" , "__USER_LABEL_PREFIX__" , "__USING_SJLJ_EXCEPTIONS__" , "__VA_ARGS__" , "__VERSION__" , "__WCHAR_MAX__" , "__WCHAR_MIN__" , "__WCHAR_TYPE__" , "__WCHAR_UNSIGNED__" , "__WINT_MAX__" , "__WINT_MIN__" , "__WINT_TYPE__" , "__XOP__" , "__XSAVEOPT__" , "__XSAVE__" , "__amd64" , "__amd64__" , "__amdfam10" , "__amdfam10__" , "__athlon" , "__athlon__" , "__athlon_sse__" , "__atom" , "__atom__" , "__bdver1" , "__bdver1__" , "__bdver2" , "__bdver2__" , "__bdver3" , "__bdver3__" , "__btver1" , "__btver1__" , "__btver2" , "__btver2__" , "__code_model_32__" , "__code_model_small__" , "__core2" , "__core2__" , "__core_avx2" , "__core_avx2__" , "__corei7" , "__corei7__" , "__cplusplus" , "__geode" , "__geode__" , "__gnu_linux__" , "__i386" , "__i386__" , "__i486" , "__i486__" , "__i586" , "__i586__" , "__i686" , "__i686__" , "__k6" , "__k6_2__" , "__k6_3__" , "__k6__" , "__k8" , "__k8__" , "__linux" , "__linux__" , "__nocona" , "__nocona__" , "__pentium" , "__pentium4" , "__pentium4__" , "__pentium__" , "__pentium_mmx__" , "__pentiumpro" , "__pentiumpro__" , "__pic__" , "__pie__" , "__tune_amdfam10__" , "__tune_athlon__" , "__tune_athlon_sse__" , "__tune_atom__" , "__tune_bdver1__" , "__tune_bdver2__" , "__tune_bdver3__" , "__tune_btver1__" , "__tune_btver2__" , "__tune_core2__" , "__tune_core_avx2__" , "__tune_corei7__" , "__tune_geode__" , "__tune_i386__" , "__tune_i486__" , "__tune_i586__" , "__tune_i686__" , "__tune_k6_2__" , "__tune_k6_3__" , "__tune_k6__" , "__tune_k8__" , "__tune_nocona__" , "__tune_pentium2__" , "__tune_pentium3__" , "__tune_pentium4__" , "__tune_pentium__" , "__tune_pentium_mmx__" , "__tune_pentiumpro__" , "__unix" , "__unix__" , "__x86_64" , "__x86_64__" , "i386" , "linux" , "unix" ]) , rAttribute = OtherTok , rIncludeAttribute = False , rDynamic = False , rCaseSensitive = True , rChildren = [] , rLookahead = False , rFirstNonspace = False , rColumn = Nothing , rContextSwitch = [] } ] , cAttribute = NormalTok , cLineEmptyContext = [] , cLineEndContext = [] , cLineBeginContext = [] , cFallthrough = False , cFallthroughContext = [] , cDynamic = False } ) ] , sAuthor = "Alex Turbov (i.zaufi@gmail.com)" , sVersion = "1" , sLicense = "LGPL" , sExtensions = [ "*.c++" , "*.cxx" , "*.cpp" , "*.cc" , "*.C" , "*.h" , "*.hh" , "*.H" , "*.h++" , "*.hxx" , "*.hpp" , "*.hcc" ] , sStartingContext = "DetectGccExtensions" }