Thu Oct 22 17:38:09 CEST 2009 r...@gamr7.com * alignment keyword support
New patches:
[alignment keyword support r...@gamr7.com**20091022153809 Ignore-this: 6bc67ccada198cb9979a0ed04a003839 ] { hunk ./src/C2HS/CHS.hs 214 Ident -- class name Ident -- name of pointer type Position + | CHSAlignment + Ident -- C type + Position instance Pos CHSHook where hunk ./src/C2HS/CHS.hs 219 + posOf (CHSAlignment _ pos) = pos posOf (CHSImport _ _ _ pos) = pos posOf (CHSContext _ _ pos) = pos posOf (CHSType _ pos) = pos hunk ./src/C2HS/CHS.hs 244 ide1 == ide2 (CHSSizeof ide1 _) == (CHSSizeof ide2 _) = ide1 == ide2 + (CHSAlignment ide1 _) == (CHSSizeof ide2 _) = + ide1 == ide2 (CHSEnum ide1 oalias1 _ _ _ _) == (CHSEnum ide2 oalias2 _ _ _ _) = oalias1 == oalias2 && ide1 == ide2 (CHSEnumDefine ide1 _ _ _) == (CHSEnumDefine ide2 _ _ _) = hunk ./src/C2HS/CHS.hs 487 showCHSHook (CHSSizeof ide _) = showString "sizeof " . showCHSIdent ide +showCHSHook (CHSAlignment ide _) = + showString "alignment " + . showCHSIdent ide showCHSHook (CHSEnum ide oalias trans oprefix derive _) = showString "enum " . showIdAlias ide oalias hunk ./src/C2HS/CHS.hs 787 parseFrags0 (CHSTokContext pos :toks) = parseContext pos toks parseFrags0 (CHSTokType pos :toks) = parseType pos toks parseFrags0 (CHSTokSizeof pos :toks) = parseSizeof pos toks + parseFrags0 (CHSTokAlignment pos :toks) = parseAlignment pos toks parseFrags0 (CHSTokEnum pos :toks) = parseEnum pos toks parseFrags0 (CHSTokCall pos :toks) = parseCall pos toks parseFrags0 (CHSTokFun pos :toks) = parseFun pos toks hunk ./src/C2HS/CHS.hs 875 return $ CHSHook (CHSSizeof ide pos) : frags parseSizeof _ toks = syntaxError toks +parseAlignment :: Position -> [CHSToken] -> CST s [CHSFrag] +parseAlignment pos (CHSTokIdent _ ide:toks) = + do + toks' <- parseEndHook toks + frags <- parseFrags toks' + return $ CHSHook (CHSAlignment ide pos) : frags +parseAlignment _ toks = syntaxError toks + parseEnum :: Position -> [CHSToken] -> CST s [CHSFrag] -- {#enum define hsid {alias_1,...,alias_n} [deriving (clid_1,...,clid_n)] #} hunk ./src/C2HS/CHS/Lexer.hs 226 | CHSTokQualif Position -- `qualified' | CHSTokSet Position -- `set' | CHSTokSizeof Position -- `sizeof' + | CHSTokAlignment Position -- `alignment' | CHSTokStable Position -- `stable' | CHSTokType Position -- `type' | CHSTok_2Case Position -- `underscoreToCase' hunk ./src/C2HS/CHS/Lexer.hs 277 posOf (CHSTokQualif pos ) = pos posOf (CHSTokSet pos ) = pos posOf (CHSTokSizeof pos ) = pos + posOf (CHSTokAlignment pos) = pos posOf (CHSTokStable pos ) = pos posOf (CHSTokType pos ) = pos posOf (CHSTok_2Case pos ) = pos hunk ./src/C2HS/CHS/Lexer.hs 328 (CHSTokQualif _ ) == (CHSTokQualif _ ) = True (CHSTokSet _ ) == (CHSTokSet _ ) = True (CHSTokSizeof _ ) == (CHSTokSizeof _ ) = True + (CHSTokAlignment _) == (CHSTokAlignment _) = True (CHSTokStable _ ) == (CHSTokStable _ ) = True (CHSTokType _ ) == (CHSTokType _ ) = True (CHSTok_2Case _ ) == (CHSTok_2Case _ ) = True hunk ./src/C2HS/CHS/Lexer.hs 380 showsPrec _ (CHSTokQualif _ ) = showString "qualified" showsPrec _ (CHSTokSet _ ) = showString "set" showsPrec _ (CHSTokSizeof _ ) = showString "sizeof" + showsPrec _ (CHSTokAlignment _ ) = showString "alignment" showsPrec _ (CHSTokStable _ ) = showString "stable" showsPrec _ (CHSTokType _ ) = showString "type" showsPrec _ (CHSTok_2Case _ ) = showString "underscoreToCase" hunk ./src/C2HS/CHS/Lexer.hs 704 idkwtok pos "qualified" _ = CHSTokQualif pos idkwtok pos "set" _ = CHSTokSet pos idkwtok pos "sizeof" _ = CHSTokSizeof pos + idkwtok pos "alignment" _ = CHSTokAlignment pos idkwtok pos "stable" _ = CHSTokStable pos idkwtok pos "type" _ = CHSTokType pos idkwtok pos "underscoreToCase" _ = CHSTok_2Case pos hunk ./src/C2HS/CHS/Lexer.hs 738 CHSTokQualif pos -> mkid pos "qualified" CHSTokSet pos -> mkid pos "set" CHSTokSizeof pos -> mkid pos "sizeof" + CHSTokAlignment pos -> mkid pos "alignment" CHSTokStable pos -> mkid pos "stable" CHSTokType pos -> mkid pos "type" CHSTok_2Case pos -> mkid pos "underscoreToCase" hunk ./src/C2HS/Gen/Bind.hs 407 traceInfoDump decl ty = traceGenBind $ "Declaration\n" ++ show decl ++ "\ntranslates to\n" ++ showExtType ty ++ "\n" +expandHook (CHSAlignment ide _) = + do + traceInfoSizeof + decl <- findAndChaseDecl ide False True -- no indirection, but shadows + (size, _) <- sizeAlignOf decl + traceInfoDump (render $ pretty decl) size + return $ show (padBits size) + where + traceInfoSizeof = traceGenBind "** alignment hook:\n" + traceInfoDump decl size = traceGenBind $ + "Alignment of declaration\n" ++ show decl ++ "\nis " + ++ show (padBits size) ++ "\n" + expandHook (CHSSizeof ide _) = do traceInfoSizeof } Context: [TAG 0.16.0 Duncan Coutts <dun...@haskell.org>**20090228132823] [c2hs no longer directly depends on alex and happy Duncan Coutts <dun...@haskell.org>**20090228132528 Only indirectly via the language-c package ] [Update AUTHORS, README and INSTALL Duncan Coutts <dun...@haskell.org>**20090228132024 Also expand tabs so it's readable irrespective of user's editor settings. ] [Add Tested-With to .cabal file Duncan Coutts <dun...@haskell.org>**20090228131950 Sadly does not work now with 6.6 and older because language-c doesn't. ] [Sort out list of modules and extra files in .cabal file Duncan Coutts <dun...@haskell.org>**20090228130247] [Fix up doc makefile and make the docbook xml validate Duncan Coutts <dun...@haskell.org>**20090228130236] [Tidy up .cabal file a bit Duncan Coutts <dun...@haskell.org>**20090228122407] [Don't need to supporess name shadowing warnings Duncan Coutts <dun...@haskell.org>**20090129120924] [Merge name shadowing patch Duncan Coutts <dun...@haskell.org>**20090129120851] [remove shadowed var warns from Text/Lexers.hs jwl...@gmail.com**20090126014744 Ignore-this: 295fa294c2086ccdf9bf8ac9ee9c89a1 ] [remove shadowed var warns from CHS.hs jwl...@gmail.com**20090126011914 Ignore-this: a27cb5927247d17c0ec91e15983fa47c ] [remove warns about unused binding in Data/Attributes.hs jwl...@gmail.com**20090126014945 Ignore-this: 2605c93006f484f1759a1afd0549f238 ] [remove shadowed var warns from CHS/Lexer.hs jwl...@gmail.com**20090126012151 Ignore-this: c2efb3ba2525aa22d71bd4b285b41d2e ] [remove shadowed var warns from Data/NameSpaces.hs jwl...@gmail.com**20090126013432 Ignore-this: 5232dd2c73c70ca5cd2557bb3fc93c4a ] [remove shadowed var warns from C2HS/C/Attrs.h jwl...@gmail.com**20090126012535 Ignore-this: 8541e3dd42bba07087bcdab75a7d41bb ] [remove shadowed var warns from Gen/Header.hs jwl...@gmail.com**20090125013702 Ignore-this: 9e66ac93508968e7ec078ec22653f8db ] [remove shadowed var warns from C/Trav.hs jwl...@gmail.com**20090125012729 Ignore-this: b8bff216cccf2cc6f8761bc50e24d0e7 ] [remove shadowed var warns from C.hs jwl...@gmail.com**20090124231253 Ignore-this: ada619fb18b4514476629ade422a6a15 ] [remove shadowed var warns from Gen/Monad.hs jwl...@gmail.com**20090124230815 Ignore-this: 36e5e06395ec108d32e85ef7254614ef ] [remove shadowd var warns from Gen/Bind.hs jwl...@gmail.com**20090124230706 Ignore-this: 5bf885e32039c5ff73703386256d234d ] [remove shadowed var warns from Main.hs jwl...@gmail.com**20090124213514 Ignore-this: 6870f2a7db0a7cf903ce3f22ec131a75 ] [Depend on language-c 0.3.1.1 benedikt.hu...@gmail.com**20090126103814 Ignore-this: b1b8c4faacf5aaa906ff00cd942f9917 ] [Use functions instead of directly constructing and matching Data.Position.Position benedikt.hu...@gmail.com**20090126102435 Ignore-this: b3db2a537db9e7f49667efb3f9a3065f ] [Constant folding for bitwise and and or. Duncan Coutts <dun...@haskell.org>**20090125163229 Patch from Achim Schneider. ] [Fix conversion of C names to Haskell names Duncan Coutts <dun...@haskell.org>**20090125162913 Names like "Foo_BarBaz" were being translated to "fooBarbaz" instead of "fooBarBaz". Also names with multiple adjacent __ characters would fail. Thanks to Achim Schneider for the patch and testing and also to Benedikt Huber for patch review. ] [Fix system tests (missing files) benedikt.hu...@gmail.com**20090124231702 Ignore-this: d27ba105c79b7bb97b27d42571b8d883 ] [Make c2hs compatible with language.c HEAD benedikt.hu...@gmail.com**20090124225918 Ignore-this: d2f38dcc57af7e7e590303f874148aa2 ] [Version nickname "Crystal Seed" Duncan Coutts <dun...@haskell.org>**20090124204007 At Benedikt's suggestion: It contains a reference to the environment (it's freezing), C would have been called Crystal if invented after Perl and Ruby, and finally, the seed (the C parser) buried in c2hs made it into a library and back into c2hs again. Seriously ;) ] [Fix file name case confusion in the call_capital test Duncan Coutts <dun...@haskell.org>**20090124202709] [Pass cpp options separately via runProcess rather than system Duncan Coutts <dun...@haskell.org>**20090124185328 Cpp options passed via the -C flag are treated as a single option. This is a change in behaviour previously flags with embeded spaces were treated separately. Most of this was done in jwlato's patch "call cpp with runProcess". This patch just merges some minor conflicts and also passes the default cpp options separately. ] [call cpp with runProcess jwl...@gmail.com**20080801224920] [Bump version number to 0.16.0 Duncan Coutts <dun...@haskell.org>**20090124181408] [Put an upper bound on the version of language-c Duncan Coutts <dun...@haskell.org>**20090124180705] [Specify the bug reports url in the .cabal file Duncan Coutts <dun...@haskell.org>**20090124180647] [Fix a load of warnings Duncan Coutts <dun...@haskell.org>**20090124180459 Not yet -Wall clean, we sill having to supress warnings about name shadowing and incomplete pattern matching. ] [Update list of copyright holders Duncan Coutts <dun...@haskell.org>**20090124180400] [Fix bug in instance Eq CHSHook Duncan Coutts <dun...@haskell.org>**20090124173108 Typo spotted via -Wall. ] [Describe enum define hooks in manual benedikt.hu...@gmail.com**20080820161740] [Add `bugs' directory in tests, and add `Capital' test benedikt.hu...@gmail.com**20080820155508] [do not normalize haskell name in a simple call hook (consistent with docs) benedikt.hu...@gmail.com**20080820155345] [Add enum define hooks benedikt.hu...@gmail.com**20080820155306] [raise error, then return empty translation unit on parse error benedikt.hu...@gmail.com**20080820155108] [c2hs.cabal: bump version, add dependency on language-c benedikt.hu...@gmail.com**20080815191010] [C2HS/CHS: Use Language.C benedikt.hu...@gmail.com**20080815190845] [C2HS/Gen: Use Language.C.Data benedikt.hu...@gmail.com**20080815190829] [CHS/Lexer: use getNameSupply / setNameSupply benedikt.hu...@gmail.com**20080815190814] [C.hs: use Language.C benedikt.hu...@gmail.com**20080815190801] [Remove Parser stuff benedikt.hu...@gmail.com**20080815190705] [Control: add getNameSupply and setNameSupply benedikt.hu...@gmail.com**20080815190638] [Data.Attributes: Use IntMap instead of Map benedikt.hu...@gmail.com**20080815190442] [src/Text: Use Language.C.Data benedikt.hu...@gmail.com**20080815190418] [tests/system: Change the Makefile to work on case insensitive systems. Document known bugs. benedikt.hu...@gmail.com**20080815184244] [tests/system: elaborate the structs and calls tests a little benedikt.hu...@gmail.com**20080815184136] [Update CHS.Lexer to use Language.C.Data benedikt.hu...@gmail.com**20080814161718] [Update C2HS.C.Trav to use Language.C benedikt.hu...@gmail.com**20080814161647] [Update C2HS.C.{Builtin,Info,Names} to use Language.C benedikt.hu...@gmail.com**20080814161546] [Update C2HS.C to use Language.C.Data. Add Show instances for Debugging purposes. benedikt.hu...@gmail.com**20080814161512] [Data.Attributes: add function to generate unused names benedikt.hu...@gmail.com**20080814161419] [src/Control: Update to use Language.C.Data benedikt.hu...@gmail.com**20080814160850] [Data: remove modules replaced by Language.C.Data benedikt.hu...@gmail.com**20080814160823] [Data.Errors: Use Language.C.Data.Error benedikt.hu...@gmail.com**20080814160759] [Data.Attributes: Use Language.C.Data.Node benedikt.hu...@gmail.com**20080814160739] [Expose liftIO in CIO.hs benedikt.hu...@gmail.com**20080814160231] [Fix dereferencing of pointers when following a path benedikt.hu...@gmail.com**20080731010424] [Support parentheses in parsePath benedikt.hu...@gmail.com**20080731005839] [Fix a non-exhaustive pattern match in Trav.hs benedikt.hu...@gmail.com**20080731005703] [Add a function which converts haskell keyword tokens into identifier tokens and use it in parsePath benedikt.hu...@gmail.com**20080731004903] [Use gcc for preprocessing on darwin benedikt.hu...@gmail.com**20080731001756] [Bump version number Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20080620223920 Just so it's different from the last released version ] [Partially convert to haddock style documentation markup Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20080620223445] [White space changes Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20080620191827 Convert tabs to spaces and remove trailing space ] [Use qualified names for System.CIO Duncan Coutts <dun...@haskell.org>**20080620173239 Always use import qualified System.CIO as CIO instead of putting a CIO suffix on everything. ] [Import System.CIO directly rather than by re-exporting Duncan Coutts <dun...@haskell.org>**20080620170755] [Use qualified names for DList module Duncan Coutts <dun...@haskell.org>**20080620163002] [Fix up module names and imports Duncan Coutts <dun...@haskell.org>**20080620161843] [Move c2hs modules under src/ Duncan Coutts <dun...@haskell.org>**20080620161108 and rename them to use hierarchical module names ] [Move the base modules under src/ Duncan Coutts <dun...@haskell.org>**20080620140132 and tests under tests/ and remove tests modules which are testing now non-existant modules. ] [Remove test code for FiniteMap module that no longer exists Duncan Coutts <dun...@haskell.org>**20080620134904] [Remove obsolete build system files Duncan Coutts <dun...@haskell.org>**20080620134539] [TAG 0.15.1 Duncan Coutts <dun...@haskell.org>**20071123165525] [Remove old empty c2hs/lib dir Duncan Coutts <dun...@haskell.org>**20071123153217] [Fix doc makefile, update INSTALL instructions and file list in .cabal file Duncan Coutts <dun...@haskell.org>**20071123153144] [bump version number to 0.15.1 Duncan Coutts <dun...@haskell.org>**20071123150204] [Update user guide and man page Duncan Coutts <dun...@haskell.org>**20071123144352 User guide converted from sgml to DocBook XML and updated for 0.15.1. Man page updated too. Includes a new makefile but there's no support for installing at the moment. We'll have to do that via cabal hooks. ] [Add lots of files to the list of stuff to go in the tarball Duncan Coutts <dun...@haskell.org>**20071121125409] [Update the install instructions Duncan Coutts <dun...@haskell.org>**20071121125339] [Make the cpp stuff work on OpenBSD Duncan Coutts <dun...@haskell.org>**20071121122604 Changes sent in by Matthias Kilian ] [Partially fix c2hs/tests Duncan Coutts <dun...@haskell.org>**20071121122436 Some tests still fail due to actual unfixed c2hs bugs. Changes sent in by Matthias Kilian. ] [Update authors list Duncan Coutts <dun...@haskell.org>**20071121121542] [Reimplement C pretty printer Bertram Felgenhauer <in...@gmx.de>**20071121084546 This is a reimplementation of the C AST pretty printer from scratch, except for the basic interface (i.e. the Pretty class). Features: - almost complete (look for FIXME and "[[[" to see which parts are not covered) - the output is valid C code. ] [Use Cabal configurations to make c2hs build with several ghc versions Bertram Felgenhauer <in...@gmx.de>**20071121081025 supports at least ghc 6.4.2, 6.6.1 and 6.8.1 ] [Add missing .h file in the tarball. Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070831110650 Change category to Development for consistency with other packages. ] [TAG 0.15.0 Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070831004657] [Update version number, name and other package meta-data Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070831002141] [Apparently OSX's cpp doesn't recognise -x c, only -x=c Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070831000649 Which is bizarre since OSX's cpp is also gnu gcc. ] [Add note to TODO about cpp directives on first line Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070726214038 cpp directives on the very first line of the .chs file are ignored because the lexer looks for \n# This is very confusing to users. ] [Remove stray debug output Duncan Coutts <dun...@haskell.org>**20070705022300] [Change the interpretation of --output and --output-dir slightly Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070604145652 To make it work better with Cabal. It's best explained by example: For --output=Foo/Bar.hs --output-dir=dist, the final file name is now dist/Foo/Bar.hs rather than dist/Bar.hs as before. Also, the .h file referred to in Bar.hs is now just "Foo/Bar.chs.h". That is, it is relative to the output file name, not with the extra output-dir prefix. This works much better with Cabal's build scheme, where generated files go into dist, and the root of the build tree is not searched for .h files instead we only have to -Idist, ie search the dir where we generated all the .chs.h files. ] [Simplify Ident representation and construction Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070601150155 The ambiguousness resolving number was not being utilised at all in c2hs so I have removed it. Similarly the parsing of lexemes was unnecessary for C identifiers and simplifying it makes the parser >10% faster. Also removed all the unused functions (of which there were many). ] [Remove CVS $Revision and $Date tags Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070531172506 they are not used by darcs so are out of date and are thus useless ] [Don't include the CHeader in the AttrC Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070531170938 AttrC should be accumulated from a sequence of external definitions rather than containing the whole CHeader from the beinning. This should make processing partial translation units easier. ] [CPtrDeclr can actually have no qualifiers Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070514133517 Remenant of the previous semantics. It used to be a non-empty list of possibly empty lists of qualifiers. Now it's just a possibly-empty list of qualifiers. So adjust the patterns to not specifially look for a non-empty qualifiers list. ] [Minimise imports Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070514004040 Using ghc's -fwarn-unused-imports ] [Remove more unused bits from the base State modules Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070513234607] [Don't rename standard monad operators Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070513233745 Don't bother providing nop, yield, (+>=), (+>), instead just use: return (), return, (>>=), (>>) ] [Remove unused fixpoint monad combinator Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070513233253 If we ever need to add this back in, we should use the standard MonadFix class ] [Remove unused mutable variable functions Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070513233043] [Remove Config module Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070513231641 It only exported one constant, which now lives in the module that uses it. ] [Don't bother putting version info into the PreCST monad Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070513225301 Just get it from the Version module when we need it. ] [Use filepath package Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070513174651 And drop the home-grown FNameOps module. ] [Pretty print ffi import strings as proper Haskell strings Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070502205232 foriegn import ccall "foo\\bar.h baz" baz :: IO () Since the import spec string is actually parsed by the compiler as a Haskell string we should use show to pretty-print it. For one thing this means that windows backslash directory separators get escaped properly "foo\\bar". ] [Emit "with" marshaling function rather than deprecated "withObject" Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070502205104] [Trivial cleanups Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070502205035] [Remove redundancy in the representation of pointer declarators Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070425052929 It was an artifact of the previous parser that we represented a whole list of pointer type modifiers in one go rather than a single ast constructor for each pointer layer as we do now. This is simpler. ] [Add a --numeric-version flag, just like ghc has Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070425044230 Should make it easier for build tools like cabal to check the c2hs version. ] [In the common case of #include'ing a single header we don't need a .chs.h file Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070425043720 So say if you do: ch2s foo.h foo.chs and you don't add any other includes in the .chs file then it's kind of annoying to have to generate this tiny .chs.h file that just contains #include "foo.h" we could instead make the ffi imports in the .hs file refer directly to foo.h rather than indirectly via foo.chs.h. Annoyingly we still have to actualy generate foo.chs.h to pass to cpp to get foo.chs.i, but we can delete foo.chs.h immediately after so the user never sees it. ] [Allow any number of .h files to be passed on the command line Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070425043340 They'll all be added to the generated .chs.h file. This will allow cabal to pass all the .h files listed in the .cabal file. ] [Use .chs.h suffix for generated header files Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070425043049 Hopefully this will not clash with user's own .h files. ] [Make the cc-wrapper program work without needing any hacking Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070420055949] [Put myself as primary author and update docs Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070420055452 I've rewritten it twice so should probably list myself as main author. It is of course derived from Manuel Chakravarty's original c2hs C parser and from James A. Roskind's C grammar and the copyright notices reflect that. We need to double check Mr Roskind's copyright license to make sure we're respecting it properly. Also remove some docs that don't really apply anymore and add a couple TODOs. ] [Add a bunch of my parser test progs Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419122317 They actually need an extra function exported from the parser to work. I'll fix that soonish. ] [Don't ignore attributes in the lexer anymore Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419121928 So now we find out if the parser really can handle __attributes__ in all the right places. It should do. I can still parse the kernel and all the core system packages on my system. ] [Allow attributes after labels Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419121506] [Allow attributes within enum, struct and union declarations Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419121352 eg: enum __attribute__ ((...)) { ... } ] [Allow attributes in parameter lists Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419121203 Before, after and between each parameter declaration. ] [Allow attributes within struct declaring lists Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419120947 Before, after and between each struct declarator. ] [Allow attrs before top level and nested declarations and type names Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419120757] [Allow attrs in most places in declarators Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419120542 in (..) parenthesis and after '*' pointers. ] [Allow attrs in decl qualifier/specifiers and after declarators. Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070419115814 This is the most common case. Note the lexer still doesn't pass attribute tokens through. ] [Rename maybe_asm -> asm_opt for naming consistency Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070415101838] [Shorten names of the GNU C __attribute__ non-terminals Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070415101545 Since we're going to be sprinkling them round the rest of the grammar it's nicer if they don't have such huge names. Also uncomment those non-terminals. ] [Rename terminal 'extension' to '__extension__' Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070415101427 That's what's it's really called anyway. ] [Apparently '\f' and '\v' are allowed in C strings and char literals Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070415075832 According to both gcc and the C99 spec. Some odd programs really use it too, like flex and binutils. ] [Allow all unnamed struct members, not just unamed nested structs Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070415075406 This does make the grammar too liberal but it's much easier to parse this more general grammar than trying to select just the unnamed nested structs. Unnamed members other than structs/unions can be checked in the AST later. It worked before, but once we introduce GNU C attributes it becomes virtually impossible to parse unambigiously. ] [Allow nested function definitions (a GNU C extension) Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070415074820 Just extends the things can can appear in compound statements, as well as statements and declarations we can have function definitions This GNU C extension is quite rarely used. ] [Deal with the scope of the 'for' loop's decl properly Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070415071342 typedef int n; // n declared as a type name for (int n = ...; ...; ...) stmt; // n now considered a normal ident n n = 0; // n reverts to being a type name the declaration can define a local var (eg 'n') that masks a type of the same name from an outer scope. The local var goes out of scope at the end of the for loop's statement, if we don't do this then we treat 'n' as a normal ident rather than a typeident after the 'for' statement. ] [TAG C parser cleanups checkpoint Duncan Coutts <duncan.cou...@worc.ox.ac.uk>**20070412071743] Patch bundle hash: 24b21470353f3ca0123bb9a5b74908875fe6b622
_______________________________________________ C2hs mailing list C2hs@haskell.org http://www.haskell.org/mailman/listinfo/c2hs