Skip to content

Commit

Permalink
Merge pull request #454 from well-typed/standard-include-path
Browse files Browse the repository at this point in the history
Use standard include directories by default
  • Loading branch information
edsko authored Feb 28, 2025
2 parents f193bb4 + 603e40f commit a80b096
Show file tree
Hide file tree
Showing 7 changed files with 69 additions and 87 deletions.
3 changes: 1 addition & 2 deletions c-expr/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -114,12 +114,11 @@ main = do
clangArgs =
case platformOS hostPlatform of
Windows -> clangArgs0
{ Clang.clangStdInc = True
}
Posix ->
clangArgs0
{ Clang.clangTarget =
Just (Clang.Target_Linux_X86_64, Clang.TargetEnvDefault)
, Clang.clangStdInc = isNothing mbHsBindgenDir
, Clang.clangSystemIncludePathDirs =
[ fromString (hsBindgenDir </> "musl-include/x86_64")
| hsBindgenDir <- maybeToList mbHsBindgenDir
Expand Down
8 changes: 4 additions & 4 deletions hs-bindgen-libclang/src/HsBindgen/Clang/Args.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,12 +37,12 @@ data ClangArgs = ClangArgs {
-- | C standard
, clangCStandard :: Maybe CStandard

-- | Enable both standard system @#include@ directories and builtin @#include@ directories (@False@ will pass @-nostdinc@)
, clangStdInc :: Bool

-- | Enable GNU extensions when 'True'
, clangEnableGnu :: Bool

-- | Enable both standard system @#include@ directories and builtin @#include@ directories (@False@ will pass @-nostdinc@)
, clangStdInc :: Bool

-- | Directories in the system include search path
, clangSystemIncludePathDirs :: [CIncludePathDir]

Expand Down Expand Up @@ -78,9 +78,9 @@ data CStandard =
defaultClangArgs :: ClangArgs
defaultClangArgs = ClangArgs {
clangTarget = Nothing
, clangStdInc = False
, clangCStandard = Nothing
, clangEnableGnu = False
, clangStdInc = True
, clangSystemIncludePathDirs = []
, clangQuoteIncludePathDirs = []
, clangOtherArgs = []
Expand Down
10 changes: 8 additions & 2 deletions hs-bindgen/app/HsBindgen/App/Cmdline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -182,7 +182,7 @@ parseClangArgs = do
-- and uses record construction (i.a. to avoid bool or string/path blindness) instead of positional one.
clangTarget <- optional parseTarget
clangCStandard <- fmap Just parseCStandard
clangStdInc <- pure True -- TODO: allow specifying --no-stdinc
clangStdInc <- fmap not parseNoStdInc
clangEnableGnu <-parseGnuOption
clangSystemIncludePathDirs <- parseSystemIncludeDirOptions
clangQuoteIncludePathDirs <- parseQuoteIncludeDirOptions
Expand Down Expand Up @@ -226,6 +226,12 @@ parseGnuOption = switch $ mconcat [
, help "Enable GNU extensions"
]

parseNoStdInc :: Parser Bool
parseNoStdInc = switch $ mconcat [
long "no-stdinc"
, help "Disable standard include directories"
]

parseSystemIncludeDirOptions :: Parser [CIncludePathDir]
parseSystemIncludeDirOptions = many . strOption $ mconcat [
long "system-include-path"
Expand Down Expand Up @@ -255,7 +261,7 @@ parseOtherArgs = many . option (eitherReader readOtherArg) $ mconcat [
| "-isystem" `List.isPrefixOf` s =
Left "System include path must be set using hs-bindgen --system-include-path options"
| s == "-nostdinc" =
Left "Option -nostdinc is always set"
Left "No standard includes option must be set using hs-bindgen --no-stdinc option"
| s == "-std" || "-std=" `List.isPrefixOf` s =
Left "C standard must be set using hs-bindgen --standard option"
| s == "--target" || "--target=" `List.isPrefixOf` s =
Expand Down
1 change: 0 additions & 1 deletion hs-bindgen/hs-bindgen.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,6 @@ library

exposed-modules:
HsBindgen.Lib
HsBindgen.TH
exposed-modules:
-- Exposed for the sake of tests
-- TODO: We should reconsider the proper way to export these.
Expand Down
92 changes: 55 additions & 37 deletions hs-bindgen/src/HsBindgen/Lib.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,9 +74,12 @@ module HsBindgen.Lib (
, contramap
, PrettyLogMsg(..)

-- * All-in-one functions
, templateHaskell
-- * Preprocessor API
, preprocessor

-- * Template Haskell API
, genBindings
, genBindings'
) where

import Data.Set qualified as Set
Expand Down Expand Up @@ -269,43 +272,9 @@ genTests
hsLineLength

{-------------------------------------------------------------------------------
All in one
Preprocessor API
-------------------------------------------------------------------------------}

templateHaskell ::
Maybe [FilePath] -- ^ System include search path directories, if @Nothing@ default ones are used.
-> [FilePath] -- ^ Quote include search path directories
-> FilePath -- ^ Input header, as written in C @#include@
-> TH.Q [TH.Dec]
templateHaskell sysIncPathDirs quoteIncPathDirs fp = do
headerIncludePath <- either fail return $ parseCHeaderIncludePath fp
src <- TH.runIO $ resolveHeader' args headerIncludePath
cheader <- TH.runIO $
withTranslationUnit nullTracer args src $
parseCHeader nullTracer SelectFromMainFile

-- record dependencies
-- TODO: https://github.com/well-typed/hs-bindgen/issues/422
TH.addDependentFile $ getSourcePath src

-- extensions checks.
-- Potential TODO: we could also check which enabled extension may interfere with the generated code. (e.g. Strict/Data)
enabledExts <- Set.fromList <$> TH.extsEnabled
let requiredExts = genExtensions headerIncludePath LowLevel.defaultTranslationOpts cheader
let missingExts = requiredExts `Set.difference` enabledExts
unless (null missingExts) $ do
TH.reportError $ "Missing LANGUAGE extensions: " ++ unwords (map show (toList missingExts))

-- generate TH declarations
genTH headerIncludePath LowLevel.defaultTranslationOpts cheader
where
args :: ClangArgs
args = defaultClangArgs {
clangStdInc = isNothing sysIncPathDirs
, clangSystemIncludePathDirs = maybe [] (map CIncludePathDir) sysIncPathDirs
, clangQuoteIncludePathDirs = CIncludePathDir <$> quoteIncPathDirs
}

preprocessor ::
[CIncludePathDir] -- ^ System include search path directories
-> [CIncludePathDir] -- ^ Non-system include search path directories
Expand Down Expand Up @@ -338,3 +307,52 @@ preprocessor sysIncPathDirs quoteIncPathDirs headerIncludePath = do
renderOpts = HsRenderOpts
{ hsLineLength = 120
}

{-------------------------------------------------------------------------------
Template Haskell API
-------------------------------------------------------------------------------}

-- | Generate bindings for the given C header
--
-- TODO: add TranslationOpts argument
genBindings ::
FilePath -- ^ Input header, as written in C @#include@
-> ClangArgs
-> TH.Q [TH.Dec]
genBindings fp args = do
headerIncludePath <- either fail return $ parseCHeaderIncludePath fp
src <- TH.runIO $ resolveHeader' args headerIncludePath
cheader <- TH.runIO $
withTranslationUnit nullTracer args src $
parseCHeader nullTracer SelectFromMainFile

-- record dependencies
-- TODO: https://github.com/well-typed/hs-bindgen/issues/422
TH.addDependentFile $ getSourcePath src

-- extensions checks.
-- Potential TODO: we could also check which enabled extension may interfere with the generated code. (e.g. Strict/Data)
enabledExts <- Set.fromList <$> TH.extsEnabled
let requiredExts = genExtensions headerIncludePath LowLevel.defaultTranslationOpts cheader
let missingExts = requiredExts `Set.difference` enabledExts
unless (null missingExts) $ do
TH.reportError $ "Missing LANGUAGE extensions: " ++ unwords (map show (toList missingExts))

-- generate TH declarations
genTH headerIncludePath LowLevel.defaultTranslationOpts cheader

-- | Generate bindings for the given C header
--
-- This function uses default Clang arguments but allows you to add directories
-- to the include search path. Use 'genBindings' when more configuration is
-- required.
genBindings' ::
[FilePath] -- ^ Quote include search path directories
-> FilePath -- ^ Input header, as written in C @#include@
-> TH.Q [TH.Dec]
genBindings' quoteIncPathDirs fp = genBindings fp args
where
args :: ClangArgs
args = defaultClangArgs {
clangQuoteIncludePathDirs = CIncludePathDir <$> quoteIncPathDirs
}
40 changes: 0 additions & 40 deletions hs-bindgen/src/HsBindgen/TH.hs

This file was deleted.

2 changes: 1 addition & 1 deletion hs-bindgen/test-th/Test01.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,4 +21,4 @@ import Language.Haskell.TH.Syntax.Compat (getPackageRoot)
import Language.Haskell.TH.Syntax (getPackageRoot)
#endif

$(getPackageRoot >>= \dir -> templateHaskell Nothing [dir </> "examples"] "test-th-01.h")
$(getPackageRoot >>= \dir -> genBindings' [dir </> "examples"] "test-th-01.h")

0 comments on commit a80b096

Please sign in to comment.