Skip to content

Commit

Permalink
feat: Ignore deprecated APIs in code generation.
Browse files Browse the repository at this point in the history
  • Loading branch information
iphydf committed Feb 18, 2025
1 parent f9be22f commit 4514b70
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 15 deletions.
3 changes: 2 additions & 1 deletion src/Apigen/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,13 +59,14 @@ runSimplify decls = do

go :: NodeF (Lexeme SId) [Sym] -> M a [Sym]
-- {-
go (PreprocInclude (L _ LitSysInclude _)) = return []
go (PreprocInclude _) = return []
go (TyPointer [ConstType (BuiltinType UInt{})]) = return []
go (TyPointer [ BuiltinType UInt{} ]) = return []
go (VarDecl [] _ []) = return []
go (FunctionPrototype [] _ _) = return []

go (PreprocIfndef (L _ _ SYM_APIGEN_IGNORE) _ es) = return es
go (PreprocIfndef (L _ _ SYM_TOX_HIDE_DEPRECATED) _ es) = return es

go (FunctionPrototype [ret] name [[BuiltinType Void]]) = return [Function ret name []]
go (FunctionPrototype [ret] name params ) = return [Function ret name (concat params)]
Expand Down
1 change: 1 addition & 0 deletions src/Apigen/Parser/SymbolNumbers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,7 @@ type TranslationUnit text = (FilePath, [Node (Lexeme text)])
builtins :: NameToSId
builtins = HashMap.fromList
[ (([], ["APIGEN","IGNORE"]), SYM_APIGEN_IGNORE)
, (([], ["TOX","HIDE","DEPRECATED"]), SYM_TOX_HIDE_DEPRECATED)
, (([], ["void" ]), TY_void )
, (([], ["char" ]), TY_char )
, (([], ["bool" ]), TY_bool )
Expand Down
31 changes: 17 additions & 14 deletions src/Apigen/Patterns.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,20 +5,23 @@ module Apigen.Patterns where
pattern SYM_APIGEN_IGNORE :: Int
pattern SYM_APIGEN_IGNORE = 0

pattern SYM_TOX_HIDE_DEPRECATED :: Int
pattern SYM_TOX_HIDE_DEPRECATED = 1

pattern TY_void, TY_char, TY_bool, TY_int8_t, TY_uint8_t, TY_int16_t, TY_uint16_t, TY_int32_t, TY_uint32_t, TY_int64_t, TY_uint64_t, TY_size_t :: Int
pattern TY_void = 1
pattern TY_char = 2
pattern TY_bool = 3
pattern TY_int8_t = 4
pattern TY_uint8_t = 5
pattern TY_int16_t = 6
pattern TY_uint16_t = 7
pattern TY_int32_t = 8
pattern TY_uint32_t = 9
pattern TY_int64_t = 10
pattern TY_uint64_t = 11
pattern TY_size_t = 12
pattern TY_void = 2
pattern TY_char = 3
pattern TY_bool = 4
pattern TY_int8_t = 5
pattern TY_uint8_t = 6
pattern TY_int16_t = 7
pattern TY_uint16_t = 8
pattern TY_int32_t = 9
pattern TY_uint32_t = 10
pattern TY_int64_t = 11
pattern TY_uint64_t = 12
pattern TY_size_t = 13

pattern SYM_abs, SYM_max :: Int
pattern SYM_abs = 13
pattern SYM_max = 14
pattern SYM_abs = 14
pattern SYM_max = 15

0 comments on commit 4514b70

Please sign in to comment.