diff --git a/CHANGES b/CHANGES index fb6f2da30..8c9884b41 100644 --- a/CHANGES +++ b/CHANGES @@ -2,6 +2,7 @@ * Add ends to locations, allowing for ranges. * Add additional expression locations to statements, etc. * Drop all support for MSVC +* Add C11 `_Generic` support. ## Older versions diff --git a/Makefile.in b/Makefile.in index df7d6f942..3be24b762 100644 --- a/Makefile.in +++ b/Makefile.in @@ -190,7 +190,6 @@ $(OBJDIR)/machdep.ml : src/machdep-ml.c configure.ac Makefile.in @echo " alignof_fun: int; (* Alignment of function *)" >> $@ @echo " alignof_aligned: int; (* Alignment of anything with the \"aligned\" attribute *)" >> $@ @echo " char_is_unsigned: bool; (* Whether \"char\" is unsigned *)">> $@ - @echo " const_string_literals: bool; (* Whether string literals have const chars *)">> $@ @echo " little_endian: bool; (* whether the machine is little endian *)">>$@ @echo " __thread_is_keyword: bool; (* whether __thread is a keyword *)">>$@ @echo " __builtin_va_list: bool; (* whether __builtin_va_list is builtin (gccism) *)">>$@ @@ -286,7 +285,7 @@ clean: $(CILLYDIR)/Makefile .PHONY: test test: - cd test; CC=@CC@ ./testcil -r --regrtest || { cat cil.log; exit 1; } + cd test; CC=@CC@ ./testcil -r --regrtest || { echo "Check test/cil.log for raw output"; exit 1; } ######################################################################## diff --git a/doc/cil.tex b/doc/cil.tex index 331494ee0..2b5fcaed1 100644 --- a/doc/cil.tex +++ b/doc/cil.tex @@ -1851,7 +1851,7 @@ \subsection{Specifying a machine model} short=2,2 int=4,4 long=8,8 long_long=8,8 pointer=8,8 enum=4,4 float=4,4 double=8,8 long_double=16,16 void=1 bool=1,1 fun=1,1 alignof_string=1 max_alignment=16 size_t=unsigned_long - wchar_t=int char_signed=true const_string_literals=true + wchar_t=int char_signed=true big_endian=false __thread_is_keyword=true __builtin_va_list=true underscore_name=true \end{verbatim} diff --git a/src/check.ml b/src/check.ml index 4615ab528..3b72fe505 100644 --- a/src/check.ml +++ b/src/check.ml @@ -208,6 +208,7 @@ let typeSigIgnoreConst (t : typ) : typsig = let attrFilter (attr : attribute) : bool = match attr with | Attr ("const", []) -> false + | Attr ("pconst", []) -> false | _ -> true in typeSigWithAttrs (List.filter attrFilter) t diff --git a/src/cil.ml b/src/cil.ml index c3a456122..34a9383b6 100755 --- a/src/cil.ml +++ b/src/cil.ml @@ -1276,8 +1276,8 @@ let charType = TInt(IChar, []) let boolType = TInt(IBool, []) let charPtrType = TPtr(charType,[]) -let charConstPtrType = TPtr(TInt(IChar, [Attr("const", [])]),[]) -let stringLiteralType = ref charPtrType +let charConstPtrType = TPtr(TInt(IChar, [Attr("const", []); Attr("pconst", [])]),[]) +let stringLiteralType = charPtrType let voidPtrType = TPtr(voidType, []) let intPtrType = TPtr(intType, []) @@ -1523,6 +1523,18 @@ let rec typeAttrs = function | TFun (_, _, _, a) -> a | TBuiltin_va_list a -> a +(** [typeAttrs], which doesn't add inner attributes. *) +let typeAttrsOuter = function + | TVoid a -> a + | TInt (_, a) -> a + | TFloat (_, a) -> a + | TNamed (_, a) -> a + | TPtr (_, a) -> a + | TArray (_, _, a) -> a + | TComp (_, a) -> a + | TEnum (_, a) -> a + | TFun (_, _, _, a) -> a + | TBuiltin_va_list a -> a let setTypeAttrs t a = match t with @@ -1574,6 +1586,19 @@ let typeRemoveAttributes (anl: string list) t = | TNamed (t, a) -> TNamed (t, drop a) | TBuiltin_va_list a -> TBuiltin_va_list (drop a) +(** Partition attributes into type qualifiers and non type qualifiers. *) +let partitionQualifierAttributes al = + List.partition (function + | Attr (("const" | "volatile" | "restrict"), []) -> true + | _ -> false + ) al + +(** Remove top-level type qualifiers from type. *) +let removeOuterQualifierAttributes t = + let a = typeAttrsOuter t in + let (_, a') = partitionQualifierAttributes a in + setTypeAttrs t a' + let unrollType (t: typ) : typ = let rec withAttrs (al: attributes) (t: typ) : typ = match t with @@ -1910,7 +1935,7 @@ let rec typeOf (e: exp) : typ = (* The type of a string is a pointer to characters ! The only case when * you would want it to be an array is as an argument to sizeof, but we * have SizeOfStr for that *) - | Const(CStr s) -> !stringLiteralType + | Const(CStr s) -> stringLiteralType | Const(CWStr s) -> TPtr(!wcharType,[]) @@ -2149,11 +2174,7 @@ let rec getInteger (e:exp) : cilint option = let mkInt ik n = Some (fst (truncateCilint ik n)) in match unrollType t, getInteger e with | TInt (ik, _), Some n -> mkInt ik n - | TPtr _, Some n -> begin - match !upointType with - TInt (ik, _) -> mkInt ik n - | _ -> raise (Failure "pointer size unknown") - end + (* "integer constant expressions" may not cast to ptr *) | TEnum (ei, _), Some n -> mkInt ei.ekind n | TFloat _, v -> v | _, _ -> None @@ -2671,9 +2692,12 @@ let isArrayType t = (** 6.3.2.3 subsection 3 * An integer constant expr with value 0, or such an expr cast to void *, is called a null pointer constant. *) -let isNullPtrConstant = function - | CastE(TPtr(TVoid _,_), e) -> isZero @@ constFold true e - | e -> isZero @@ constFold true e +let isNullPtrConstant e = + let rec isNullPtrConstant = function + | CastE (TPtr (TVoid [], []), e) -> isNullPtrConstant e (* no qualifiers allowed on void or ptr *) + | e -> isZero e + in + isNullPtrConstant (constFold true e) let rec isConstant = function | Const _ -> true @@ -2798,7 +2822,7 @@ let initGccBuiltins () : unit = let ulongLongType = TInt(IULongLong, []) in let floatType = TFloat(FFloat, []) in let longDoubleType = TFloat (FLongDouble, []) in - let voidConstPtrType = TPtr(TVoid [Attr ("const", [])], []) in + let voidConstPtrType = TPtr(TVoid [Attr ("const", []); Attr ("pconst", [])], []) in let sizeType = !typeOfSizeOf in let v4sfType = TFloat (FFloat,[Attr("__vector_size__", [AInt 16])]) in @@ -4176,7 +4200,7 @@ class defaultCilPrinterClass : cilPrinter = object (self) | TArray (elemt, lo, a) -> (* ignore the const attribute for arrays *) - let a' = dropAttributes [ "const" ] a in + let a' = dropAttributes [ "pconst" ] a in let name' = if a' == [] then name else if nameOpt == None then printAttributes a' else @@ -4241,7 +4265,8 @@ class defaultCilPrinterClass : cilPrinter = object (self) method pAttr (Attr(an, args): attribute) : doc * bool = (* Recognize and take care of some known cases *) match an, args with - "const", [] -> text "const", false + "const", [] -> nil, false (* don't print const directly, because of split local declarations *) + | "pconst", [] -> text "const", false (* pconst means print const *) (* Put the aconst inside the attribute list *) | "complex", [] when !c99Mode -> text "_Complex", false | "complex", [] -> text "__complex__", false @@ -4805,7 +4830,7 @@ let makeVarinfo global name ?init typ = { vname = name; vid = newVID (); vglob = global; - vtype = if global then typ else typeRemoveAttributes ["const"] typ; + vtype = if global then typ else typeRemoveAttributes ["pconst"] typ; vdecl = lu; vinit = {init=init}; vinline = false; @@ -6712,11 +6737,6 @@ let initCIL () = Some machine -> M.theMachine := machine | None -> M.theMachine := M.gcc end; - (* Pick type for string literals *) - stringLiteralType := if !M.theMachine.M.const_string_literals then - charConstPtrType - else - charPtrType; (* Find the right ikind given the size *) let findIkindSz (unsigned: bool) (sz: int) : ikind = try diff --git a/src/cil.mli b/src/cil.mli index 7ad9548e3..b4afa6c7f 100644 --- a/src/cil.mli +++ b/src/cil.mli @@ -1332,6 +1332,9 @@ val charType: typ (** char * *) val charPtrType: typ +(** Type of string literals *) +val stringLiteralType: typ + (** wchar_t (depends on architecture) and is set when you call * {!Cil.initCIL}. *) val wcharKind: ikind ref @@ -1799,6 +1802,9 @@ val hasAttribute: string -> attributes -> bool of the type structure, in case of composite, enumeration and named types *) val typeAttrs: typ -> attribute list +(** [typeAttrs], which doesn't add inner attributes. *) +val typeAttrsOuter: typ -> attribute list + val setTypeAttrs: typ -> attributes -> typ (* Resets the attributes *) @@ -1811,6 +1817,13 @@ val typeAddAttributes: attribute list -> typ -> typ val typeRemoveAttributes: string list -> typ -> typ +(** Partition attributes into type qualifiers and non type qualifiers. *) +val partitionQualifierAttributes: attribute list -> attribute list * attribute list + +(** Remove top-level type qualifiers from type. *) +val removeOuterQualifierAttributes: typ -> typ + + (** Convert an expression into an attrparam, if possible. Otherwise raise NotAnAttrParam with the offending subexpression *) val expToAttrParam: exp -> attrparam diff --git a/src/frontc/cabs.ml b/src/frontc/cabs.ml index 81bf8e0d7..0f0409541 100644 --- a/src/frontc/cabs.ml +++ b/src/frontc/cabs.ml @@ -83,6 +83,7 @@ type typeSpecifier = (* Merge all specifiers into one type *) | Tenum of string * enum_item list option * attribute list | TtypeofE of expression (* GCC __typeof__ *) | TtypeofT of specifier * decl_type (* GCC __typeof__ *) + | Tdefault (** "default" in generic associations *) and storage = NO_STORAGE | AUTO | STATIC | EXTERN | REGISTER @@ -280,6 +281,7 @@ and expression = | MEMBEROFPTR of expression * string | GNU_BODY of block | EXPR_PATTERN of string (* pattern variable, and name *) + | GENERIC of expression * (((specifier * decl_type) * expression) list) and constant = | CONST_INT of string (* the textual representation *) diff --git a/src/frontc/cabs2cil.ml b/src/frontc/cabs2cil.ml index 6fd0463c2..844538031 100644 --- a/src/frontc/cabs2cil.ml +++ b/src/frontc/cabs2cil.ml @@ -603,11 +603,7 @@ let alphaConvertVarAndAddToEnv (addtoenv: bool) (vi: varinfo) : varinfo = * a struct we must recursively strip the "const" from fields and array * elements. *) let rec stripConstLocalType (t: typ) : typ = - let dc a = - if hasAttribute "const" a then - dropAttribute "const" a - else a - in + let dc = dropAttribute "pconst" in match t with | TPtr (bt, a) -> (* We want to be able to detect by pointer equality if the type has @@ -1570,7 +1566,16 @@ type combineWhat = * that are known to be equal *) let isomorphicStructs : (string * string, bool) H.t = H.create 15 +(** Construct the composite type of [oldt] and [t] if they are compatible. + Raise [Failure] if they are incompatible. *) let rec combineTypes (what: combineWhat) (oldt: typ) (t: typ) : typ = + let (oldq, olda) = partitionQualifierAttributes (typeAttrsOuter oldt) in + let (q, a) = partitionQualifierAttributes (typeAttrsOuter t) in + if oldq <> q then + raise (Failure "different type qualifiers") + else if q <> [] then + cabsTypeAddAttributes q (combineTypes what (setTypeAttrs oldt olda) (setTypeAttrs t a)) + else match oldt, t with | TVoid olda, TVoid a -> TVoid (cabsAddAttributes olda a) | TInt (oldik, olda), TInt (ik, a) -> @@ -1743,7 +1748,7 @@ let rec combineTypes (what: combineWhat) (oldt: typ) (t: typ) : typ = combineTypes (if what = CombineFundef then CombineFunarg else CombineOther) - ot' at + (removeOuterQualifierAttributes ot') (removeOuterQualifierAttributes at) in let a = addAttributes oa aa in (n, t, a)) @@ -1883,19 +1888,33 @@ let conditionalConversion (t2: typ) (t3: typ) (e2: exp option) (e3:exp) : typ = arithmeticConversion t2 t3 | TComp (comp2,_), TComp (comp3,_), _ when comp2.ckey = comp3.ckey -> t2 - | TPtr(_, _), TPtr(TVoid _, _), _ -> - if isNullPtrConstant e3 then t2 else t3 - | TPtr(TVoid _, _), TPtr(_, _), Some e2' -> - if isNullPtrConstant e2' then t3 else t2 + | TVoid [], TVoid [], _ -> TVoid [] (* TODO: what about qualifiers? standard says nothing *) + | TPtr(_, _), _, _ when isNullPtrConstant e3 -> t2 + | _, TPtr(_, _), Some e2' when isNullPtrConstant e2' -> t3 + | TPtr(b2, _), TPtr(TVoid _ as b3, _), _ + | TPtr(TVoid _ as b2, _), TPtr(b3, _), _ -> + let a2 = typeAttrsOuter b2 in + let a3 = typeAttrsOuter b3 in + let (q2, _) = partitionQualifierAttributes a2 in + let (q3, _) = partitionQualifierAttributes a3 in + let q = cabsAddAttributes q2 q3 in + TPtr (TVoid q, []) | TPtr _, TPtr _, _ when Util.equals (typeSig t2) (typeSig t3) -> t2 - | TPtr _, TInt _, _ -> t2 (* most likely comparison with int constant 0, if it isn't it would not be valid C *) - | TInt _, TPtr _, _ -> t3 (* most likely comparison with int constant 0, if it isn't it would not be valid C *) + | TPtr _, TInt _, _ -> t2 (* not "null pointer constant", not allowed by standard, works in gcc/clang with warning *) + | TInt _, TPtr _, _ -> t3 (* not "null pointer constant", not allowed by standard, works in gcc/clang with warning *) (* When we compare two pointers of different type, we combine them * using the same algorithm when combining multiple declarations of * a global *) - | (TPtr _) as t2', (TPtr _ as t3'), _ -> begin - try combineTypes CombineOther t2' t3' + | TPtr (b2, _), TPtr (b3, _), _ -> begin + try + let a2 = typeAttrsOuter b2 in + let a3 = typeAttrsOuter b3 in + let (q2, a2') = partitionQualifierAttributes a2 in + let (q3, a3') = partitionQualifierAttributes a3 in + let b = combineTypes CombineOther (setTypeAttrs b2 a2') (setTypeAttrs b2 a3') in + let q = cabsAddAttributes q2 q3 in + TPtr (cabsTypeAddAttributes q b, []) with Failure msg -> begin ignore (warn "A.QUESTION: %a does not match %a (%s)" d_type (unrollType t2) d_type (unrollType t3) msg); @@ -2443,6 +2462,7 @@ let rec doSpecList (suggestedAnonName: string) (* This string will be part of | [A.Tfloat128] -> TFloat(FLongDouble, []) (* TODO: Correct? *) (* Now the other type specifiers *) + | [A.Tdefault] -> E.s (error "Default outside generic associations") | [A.Tnamed n] -> begin if n = "__builtin_va_list" && !Machdep.theMachine.Machdep.__builtin_va_list then begin @@ -2629,7 +2649,7 @@ let rec doSpecList (suggestedAnonName: string) (* This string will be part of and convertCVtoAttr (src: A.cvspec list) : A.attribute list = match src with | [] -> [] - | CV_CONST :: tl -> ("const",[]) :: (convertCVtoAttr tl) + | CV_CONST :: tl -> ("const",[]) :: ("pconst",[]) :: (convertCVtoAttr tl) | CV_VOLATILE :: tl -> ("volatile",[]) :: (convertCVtoAttr tl) | CV_RESTRICT :: tl -> ("restrict",[]) :: (convertCVtoAttr tl) | CV_COMPLEX :: tl -> ("complex",[]) :: (convertCVtoAttr tl) @@ -4798,6 +4818,35 @@ and doExp (asconst: bool) (* This expression is used as a constant *) | A.EXPR_PATTERN _ -> E.s (E.bug "EXPR_PATTERN in cabs2cil input") + | A.GENERIC (e, al) -> + let is_default = function + | ([SpecType Tdefault], JUSTBASE) -> true (* exactly matches cparser *) + | _ -> false + in + let (al_default, al_nondefault) = List.partition (fun (at, _) -> is_default at) al in + + let typ_compatible t1 t2 = + match combineTypes CombineOther t1 t2 with (* combineTypes does "compatible types" check *) + | _ -> true + | exception (Failure _) -> false + in + let (_, _, e_typ) = doExp false e (AExp None) in (* doExp with AExp handles array and function types for "lvalue conversions" (AType would not!) *) + let e_typ = removeOuterQualifierAttributes e_typ in (* removeOuterQualifierAttributes handles qualifiers for "lvalue conversions" *) + let al_compatible = List.filter (fun ((ast, adt), _) -> typ_compatible e_typ (doOnlyType ast adt)) al_nondefault in + + (* TODO: error when multiple compatible associations or defaults even when unused? *) + + begin match al_compatible with + | [(_, ae)] -> doExp false ae (AExp None) + | [] -> + begin match al_default with + | [(_, ae)] -> doExp false ae (AExp None) + | [] -> E.s (error "No compatible associations or default in generic") + | _ -> E.s (error "Multiple defaults in generic") + end + | _ -> E.s (error "Multiple compatible associations in generic") + end + with e when continueOnError -> begin (*ignore (E.log "error in doExp (%s)" (Printexc.to_string e));*) E.hadErrors := true; diff --git a/src/frontc/cabsvisit.ml b/src/frontc/cabsvisit.ml index 834df080c..49540b244 100644 --- a/src/frontc/cabsvisit.ml +++ b/src/frontc/cabsvisit.ml @@ -526,6 +526,17 @@ and childrenExpression vis e = let b' = visitCabsBlock vis b in if b' != b then GNU_BODY b' else e | EXPR_PATTERN _ -> e + | GENERIC (e1, al) -> + let e1' = ve e1 in + let al' = mapNoCopy (fun (((ast, adt), ae) as a) -> + let ast' = visitCabsSpecifier vis ast in + let adt' = visitCabsDeclType vis false adt in + let ae' = ve ae in + if ast' != ast || adt' != adt || ae' != ae then ((ast', adt'), ae') else a + ) al + in + if e1' != e1 || al' != al then GENERIC (e1', al') else e + and visitCabsInitExpression vis (ie: init_expression) : init_expression = doVisit vis vis#vinitexpr childrenInitExpression ie diff --git a/src/frontc/clexer.mll b/src/frontc/clexer.mll index f31afbabb..b4f78fd2a 100644 --- a/src/frontc/clexer.mll +++ b/src/frontc/clexer.mll @@ -211,6 +211,7 @@ let init_lexicon _ = THREAD loc else IDENT ("__thread", loc)); + ("_Generic", fun loc -> GENERIC loc); ] (* Mark an identifier as a type name. The old mapping is preserved and will diff --git a/src/frontc/cparser.mly b/src/frontc/cparser.mly index b383720b2..5dac0b42c 100644 --- a/src/frontc/cparser.mly +++ b/src/frontc/cparser.mly @@ -252,6 +252,7 @@ let transformOffsetOf (speclist, dtype) member = %token EOF %token CHAR INT BOOL DOUBLE FLOAT VOID INT64 INT32 %token INT128 FLOAT128 COMPLEX /* C99 */ +%token GENERIC /* C11 */ %token ENUM STRUCT TYPEDEF UNION %token SIGNED UNSIGNED LONG SHORT %token VOLATILE EXTERN STATIC CONST RESTRICT AUTO REGISTER @@ -469,8 +470,19 @@ primary_expression: /*(* 6.5.1. *)*/ /*(* Next is Scott's transformer *)*/ | AT_EXPR LPAREN IDENT RPAREN /* expression pattern variable */ { EXPR_PATTERN(fst $3), $1 } +| GENERIC LPAREN assignment_expression COMMA generic_assoc_list RPAREN {GENERIC ((fst $3), $5), $1} ; +/* (specifier, expression) list */ +generic_assoc_list: +| generic_association {[$1]} +| generic_assoc_list COMMA generic_association {$3 :: $1} + +/* specifier, expression */ +generic_association: +| type_name COLON assignment_expression {($1, fst $3)} +| DEFAULT COLON assignment_expression {([SpecType Tdefault], JUSTBASE), fst $3} + postfix_expression: /*(* 6.5.2 *)*/ | primary_expression { $1 } diff --git a/src/frontc/cprint.ml b/src/frontc/cprint.ml index f6c6f52e9..3e7b052ef 100644 --- a/src/frontc/cprint.ml +++ b/src/frontc/cprint.ml @@ -186,6 +186,7 @@ and print_type_spec = function (print_enum_items enum_items) | TtypeofE e -> printl ["__typeof__";"("]; print_expression e; print ") " | TtypeofT (s,d) -> printl ["__typeof__";"("]; print_onlytype (s, d); print ") " + | Tdefault -> print "default " (* TODO: is this right? *) (* print "struct foo", but with specified keyword and a list of @@ -393,6 +394,7 @@ and get_operator exp = | TYPE_SIZEOF _ -> ("", 16) | EXPR_ALIGNOF exp -> ("", 16) | TYPE_ALIGNOF _ -> ("", 16) + | GENERIC _ -> ("", 16) (* TODO: is this right? *) | IMAG exp -> ("", 16) | REAL exp -> ("", 16) | CLASSIFYTYPE exp -> ("", 16) @@ -528,6 +530,21 @@ and print_expression_level (lvl: int) (exp : expression) = printl ["__alignof__";"("]; print_onlytype (bt, dt); print ")" + | GENERIC (exp, lst) -> + let rec print_generic_list l = + match l with + [] -> () + | (t, e) :: tl -> + print ", "; + print_onlytype t; + print ": "; + print_expression_level 0 e; + print_generic_list tl + in + printl ["_Generic";"("]; + print_expression_level 0 exp; + print_generic_list lst; + print ")" | IMAG exp -> printl ["__imag__";"("]; print_expression_level 0 exp; diff --git a/src/machdep-ml.c.in b/src/machdep-ml.c.in index 698337e3a..19816f49a 100644 --- a/src/machdep-ml.c.in +++ b/src/machdep-ml.c.in @@ -67,7 +67,6 @@ typedef int bool; #ifdef _GNUCC #define LONGLONG long long -#define CONST_STRING_LITERALS "true" #define VERSION __VERSION__ #define VERSION_MAJOR __GNUC__ #define VERSION_MINOR __GNUC_MINOR__ @@ -253,7 +252,7 @@ int main(int argc, char **argv) printf("short=%d,%d int=%d,%d long=%d,%d long_long=%d,%d pointer=%d,%d " "alignof_enum=%d float=%d,%d double=%d,%d long_double=%d,%d float_complex=%d,%d double_complex=%d,%d long_double_complex=%d,%d void=%d " "bool=%d,%d fun=%d,%d alignof_string=%d max_alignment=%d size_t=%s " - "wchar_t=%s char_signed=%s const_string_literals=%s " + "wchar_t=%s char_signed=%s " "big_endian=%s __thread_is_keyword=%s __builtin_va_list=%s " "underscore_name=%s\n", (int)sizeof(short), alignof_short, (int)sizeof(int), alignof_int, @@ -265,7 +264,7 @@ int main(int argc, char **argv) (int)sizeof(bool), alignof_bool, sizeof_fun, alignof_fun, alignof_str, alignof_aligned, underscore(TYPE_SIZE_T), underscore(TYPE_WCHAR_T), - char_is_unsigned ? "false" : "true", CONST_STRING_LITERALS, + char_is_unsigned ? "false" : "true", little_endian ? "false" : "true", THREAD_IS_KEYWORD, HAVE_BUILTIN_VA_LIST, UNDERSCORE_NAME); } @@ -312,7 +311,6 @@ int main(int argc, char **argv) printf("\t alignof_fun = %d;\n", alignof_fun); printf("\t alignof_aligned = %d;\n", alignof_aligned); printf("\t char_is_unsigned = %s;\n", char_is_unsigned ? "true" : "false"); - printf("\t const_string_literals = %s;\n", CONST_STRING_LITERALS); printf("\t underscore_name = %s;\n", UNDERSCORE_NAME); printf("\t __builtin_va_list = %s;\n", HAVE_BUILTIN_VA_LIST); printf("\t __thread_is_keyword = %s;\n", THREAD_IS_KEYWORD); diff --git a/src/machdepenv.ml b/src/machdepenv.ml index 2707946b7..1a8cad214 100644 --- a/src/machdepenv.ml +++ b/src/machdepenv.ml @@ -89,7 +89,6 @@ let modelParse (s:string) : mach = size_t = respace (getNthString 0 entries "size_t"); wchar_t = respace (getNthString 0 entries "wchar_t"); char_is_unsigned = not (getBool entries "char_signed"); - const_string_literals = getBool entries "const_string_literals"; little_endian = not (getBool entries "big_endian"); __thread_is_keyword = getBool entries "__thread_is_keyword"; __builtin_va_list = getBool entries "__builtin_va_list"; diff --git a/src/mergecil.ml b/src/mergecil.ml index e5dfe5ba4..2da60036b 100644 --- a/src/mergecil.ml +++ b/src/mergecil.ml @@ -437,9 +437,18 @@ type combineWhat = | CombineOther +(** Construct the composite type of [oldt] and [t] if they are compatible. + Raise [Failure] if they are incompatible. *) let rec combineTypes (what: combineWhat) (oldfidx: int) (oldt: typ) (fidx: int) (t: typ) : typ = + let (oldq, olda) = partitionQualifierAttributes (typeAttrsOuter oldt) in + let (q, a) = partitionQualifierAttributes (typeAttrsOuter t) in + if oldq <> q then + raise (Failure (P.sprint ~width:80 (P.dprintf "(different type qualifiers %a and %a)" d_attrlist oldq d_attrlist q))) + else if q <> [] then + typeAddAttributes q (combineTypes what oldfidx (setTypeAttrs oldt olda) fidx (setTypeAttrs t a)) + else match oldt, t with | TVoid olda, TVoid a -> TVoid (addAttributes olda a) | TInt (oldik, olda), TInt (ik, a) -> @@ -552,7 +561,7 @@ let rec combineTypes (what: combineWhat) combineTypes (if what = CombineFundef then CombineFunarg else CombineOther) - oldfidx ot fidx at + oldfidx (removeOuterQualifierAttributes ot) fidx (removeOuterQualifierAttributes at) in let a = addAttributes oa aa in (n, t, a)) @@ -811,8 +820,10 @@ let oneFilePass1 (f:file) : unit = * can happen if one file declares the variable a non-const while * others declare it as "const". *) if hasAttribute "const" (typeAttrs vi.vtype) != - hasAttribute "const" (typeAttrs oldvi.vtype) then begin - newrep.ndata.vtype <- typeRemoveAttributes ["const"] newtype; + hasAttribute "const" (typeAttrs oldvi.vtype) || + hasAttribute "pconst" (typeAttrs vi.vtype) != + hasAttribute "pconst" (typeAttrs oldvi.vtype) then begin + newrep.ndata.vtype <- typeRemoveAttributes ["const"; "pconst"] newtype; end else begin newrep.ndata.vtype <- newtype; end; diff --git a/test/Makefile b/test/Makefile index a5a09775d..abd04f997 100644 --- a/test/Makefile +++ b/test/Makefile @@ -193,6 +193,18 @@ testrunc99/% : $(SMALL1)/%.c cd $(SMALL1); ./$*.exe echo SUCCESS +# TODO: how to make this just run cil, not gcc? +testc11/% : $(SMALL1)/%.c + cd $(SMALL1); $(CILLY) --nomerge --commPrintLn \ + $(CFLAGS) -std=c11 $(EXEOUT)$*.exe $*.c -lm + echo SUCCESS + +testrunc11/% : $(SMALL1)/%.c + cd $(SMALL1); $(CILLY) --nomerge --commPrintLn \ + $(CFLAGS) -std=c11 $(EXEOUT)$*.exe $*.c -lm + cd $(SMALL1); ./$*.exe + echo SUCCESS + testrungcc/% : $(SMALL1)/%.c mustbegcc cd $(SMALL1); $(CILLY) --nomerge --commPrintLn \ $(CFLAGS) $(EXEOUT)$*.exe $*.c diff --git a/test/small1/c11-generic.c b/test/small1/c11-generic.c new file mode 100644 index 000000000..184b80e07 --- /dev/null +++ b/test/small1/c11-generic.c @@ -0,0 +1,35 @@ +#include "testharness.h" +#define type1(x) _Generic((x), char: 1, unsigned int:2, default:0) +#define type2(x) _Generic((x), char: 1, unsigned int:2, const int:3, default:0) +#define type3(x) _Generic((x), int:1, const int:2, default:0) +#define type4(x) _Generic((x), char*:1, char[4]:0) +#define type5(x) _Generic((x), int*: 1, default: 0) + +int main() { + unsigned char v_uchar; + char v_char; + int v_int; + const int v_intconst; + + if(type1(v_int) != 0) { E(1); } + if(type1(v_uchar) != 0) { E(2); } + if(type1(v_char) != 1) { E(3); } + + if(type2(v_int) != 0) { E(4); } + if(type2(v_intconst) != 0) { E(5); } + + if(type3(v_int) != 1) { E(6); } + if(type3(v_intconst) != 1) { E(7); } + + if(type3((const int)v_int) != 1) { E(8); } + if(type3((const int)v_intconst) != 1) { E(9); } + + if (type5(&v_int) != 1) { E(11); } + + if((type4("abcd")) != 1) { E(10); } + + // no parenthesis in generic exp, due to broken GENERIC Cabsvisit, Cabs2cil.stripParenFile used to replace the entire generc with the exp 1, not the default 0 + if (_Generic(1, default: 0) != 0) { E(12); } + + SUCCESS; +} diff --git a/test/small1/clang-c11-generic-1-1.c b/test/small1/clang-c11-generic-1-1.c new file mode 100644 index 000000000..313929672 --- /dev/null +++ b/test/small1/clang-c11-generic-1-1.c @@ -0,0 +1,8 @@ +// https://github.com/llvm/llvm-project/blob/d480f968ad8b56d3ee4a6b6df5532d485b0ad01e/clang/test/Sema/generic-selection.c + +int main() { + (void) _Generic((void (*)()) 0, + void (*)(int): 0, + void (*)(void): 0); + return 0; +} diff --git a/test/small1/clang-c11-generic-1-2.c b/test/small1/clang-c11-generic-1-2.c new file mode 100644 index 000000000..2235c51b1 --- /dev/null +++ b/test/small1/clang-c11-generic-1-2.c @@ -0,0 +1,7 @@ +// https://github.com/llvm/llvm-project/blob/d480f968ad8b56d3ee4a6b6df5532d485b0ad01e/clang/test/Sema/generic-selection.c + +int main() { + (void) _Generic(0, + char: 0, short: 0, long: 0); + return 0; +} diff --git a/test/small1/clang-c11-generic-2.c b/test/small1/clang-c11-generic-2.c new file mode 100644 index 000000000..96386dd15 --- /dev/null +++ b/test/small1/clang-c11-generic-2.c @@ -0,0 +1,14 @@ +// https://github.com/llvm/llvm-project/blob/d480f968ad8b56d3ee4a6b6df5532d485b0ad01e/clang/test/Sema/conditional.c + +int main() { + _Generic(0 ? (int const *)0 : (void *)0, int const *: (void)0); + _Generic(0 ? (int const *)0 : (void *)1, void const *: (void)0); + _Generic(0 ? (int volatile*)0 : (void const*)1, void volatile const*: (void)0); + _Generic(0 ? (int volatile*)0 : (void const*)0, void volatile const*: (void)0); + + // added here + _Generic(0 ? (const int*)0 : (volatile int*)0, const volatile int*: (void)0); + _Generic(0 ? (int const *)0 : 0, int const *: (void)0); + _Generic(0 ? (int const *)0 : 1, int const *: (void)0); // not allowed by standard, works in gcc/clang with warning + return 0; +} diff --git a/test/small1/decl1.c b/test/small1/decl1.c deleted file mode 100644 index 9c05f2161..000000000 --- a/test/small1/decl1.c +++ /dev/null @@ -1,20 +0,0 @@ -struct timeval { - int tv_sec; - int tv_usec; -}; - -extern struct timeval xtime; - - -volatile struct timeval xtime __attribute__ ((aligned (16))); - -extern void printf(char *, ...); -#define E(n) { printf("Error %d\n", n); return n; } - - -int main() { - if((int)&xtime & 0xF != 0) E(1); - - printf("Success\n"); - return 0; -} diff --git a/test/small1/gcc-c11-generic-1.c b/test/small1/gcc-c11-generic-1.c new file mode 100644 index 000000000..439ca004b --- /dev/null +++ b/test/small1/gcc-c11-generic-1.c @@ -0,0 +1,63 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-1.c +#include "testharness.h" + +// _Noreturn extern void abort (void); + +int e = 0; + +void +check (int n) +{ + e++; + if (n) + E(e); +} + +void f (void) { + +} + +int +main (void) +{ + int n = 0; + + check (_Generic (n++, int: 0)); + /* _Generic should not evaluate its argument. */ + check (n); + + check (_Generic (n, double: n++, default: 0)); + check (n); + + /* Qualifiers are removed for the purpose of type matching. */ + const int cn = 0; + check (_Generic (cn, int: 0, default: n++)); + check (n); + check (_Generic ((const int) n, int: 0, default: n++)); + check (n); + + /* Arrays decay to pointers. */ + int a[1]; + const int ca[1]; + check (_Generic (a, int *: 0, const int *: n++)); + check (n); + check (_Generic (ca, const int *: 0, int *: n++)); + check (n); // TODO: fix, CIL moves ca up and recursively strips const + + /* Functions decay to pointers. */ + // extern void f (void); // made non-extern above to compile + check (_Generic (f, void (*) (void): 0, default: n++)); + check (n); + + /* _Noreturn is not part of the function type. */ + // TODO: add back when C11 _Noreturn supported + /* check (_Generic (&abort, void (*) (void): 0, default: n++)); + check (n); */ + + /* Integer promotions do not occur. */ + short s; + check (_Generic (s, short: 0, int: n++)); + check (n); + + SUCCESS; +} diff --git a/test/small1/gcc-c11-generic-2-1.c b/test/small1/gcc-c11-generic-2-1.c new file mode 100644 index 000000000..5b8e64c58 --- /dev/null +++ b/test/small1/gcc-c11-generic-2-1.c @@ -0,0 +1,12 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-2.c + +void +f (int n) +{ + /* Multiple 'default's. */ + _Generic (n, default: 1, default: 2); +} + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-2-2.c b/test/small1/gcc-c11-generic-2-2.c new file mode 100644 index 000000000..dfa8e337f --- /dev/null +++ b/test/small1/gcc-c11-generic-2-2.c @@ -0,0 +1,12 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-2.c + +void +f (int n) +{ + /* Variably-modified type not ok. */ + _Generic (n, int[n]: 0, default: 1); +} + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-2-3.c b/test/small1/gcc-c11-generic-2-3.c new file mode 100644 index 000000000..b7911ef72 --- /dev/null +++ b/test/small1/gcc-c11-generic-2-3.c @@ -0,0 +1,14 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-2.c + +struct incomplete; + +void +f (int n) +{ + /* Type must be complete. */ + _Generic (n, struct incomplete: 0, default: 1); +} + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-2-4.c b/test/small1/gcc-c11-generic-2-4.c new file mode 100644 index 000000000..9ed68ed5b --- /dev/null +++ b/test/small1/gcc-c11-generic-2-4.c @@ -0,0 +1,12 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-2.c + +void +f (int n) +{ + /* Type must be complete. */ + _Generic (n, void: 0, default: 1); +} + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-2-5.c b/test/small1/gcc-c11-generic-2-5.c new file mode 100644 index 000000000..540ace329 --- /dev/null +++ b/test/small1/gcc-c11-generic-2-5.c @@ -0,0 +1,12 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-2.c + +void +f (int n) +{ + /* Type must be object type. */ + _Generic (n, void (void): 0, default: 1); +} + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-2-6.c b/test/small1/gcc-c11-generic-2-6.c new file mode 100644 index 000000000..563d7e09b --- /dev/null +++ b/test/small1/gcc-c11-generic-2-6.c @@ -0,0 +1,12 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-2.c + +void +f (int n) +{ + /* Two compatible types in association list. */ + _Generic (&n, int: 5, signed int: 7, default: 23); +} + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-2-7.c b/test/small1/gcc-c11-generic-2-7.c new file mode 100644 index 000000000..5d006287a --- /dev/null +++ b/test/small1/gcc-c11-generic-2-7.c @@ -0,0 +1,12 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-2.c + +void +f (int n) +{ + /* No matching association. */ + _Generic (n, void *: 5); +} + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-3-1.c b/test/small1/gcc-c11-generic-3-1.c new file mode 100644 index 000000000..28e8e9644 --- /dev/null +++ b/test/small1/gcc-c11-generic-3-1.c @@ -0,0 +1,9 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-3.c + +char const *a = _Generic ("bla", char *: ""); +char const *c = _Generic ((int const) { 0 }, int: ""); +char const *e = _Generic (+(int const) { 0 }, int: ""); + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-3-2.c b/test/small1/gcc-c11-generic-3-2.c new file mode 100644 index 000000000..b43477cda --- /dev/null +++ b/test/small1/gcc-c11-generic-3-2.c @@ -0,0 +1,7 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-3.c + +char const *b = _Generic ("bla", char[4]: ""); + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-3-3.c b/test/small1/gcc-c11-generic-3-3.c new file mode 100644 index 000000000..511b346b4 --- /dev/null +++ b/test/small1/gcc-c11-generic-3-3.c @@ -0,0 +1,7 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-3.c + +char const *d = _Generic ((int const) { 0 }, int const: ""); + +int main() { + return 0; +} diff --git a/test/small1/gcc-c11-generic-3-4.c b/test/small1/gcc-c11-generic-3-4.c new file mode 100644 index 000000000..54b6ae851 --- /dev/null +++ b/test/small1/gcc-c11-generic-3-4.c @@ -0,0 +1,7 @@ +// https://github.com/gcc-mirror/gcc/blob/16e2427f50c208dfe07d07f18009969502c25dc8/gcc/testsuite/gcc.dg/c11-generic-3.c + +char const *f = _Generic (+(int const) { 0 }, int const: ""); + +int main() { + return 0; +} diff --git a/test/testcil.pl b/test/testcil.pl index c21fddd3c..38d9c004f 100644 --- a/test/testcil.pl +++ b/test/testcil.pl @@ -404,7 +404,6 @@ sub addToGroup { addTest("testrun/lval1 _GNUCC=1"); #MIA: addTest("test/bind2 EXTRAARGS=--allowInlineAssembly"); #addToGroup("test/bind2", "slow"); -addTest("testrun/decl1 _GNUCC=1"); addTest("testrun/addr-array"); addTest("testrun/addr-string"); addTest("combine1 "); @@ -694,6 +693,23 @@ sub addToGroup { addTest("combinec99inline"); addBadComment("combinec99inline", "C99 inline semantic not fully supported."); +addTest("testrunc11/c11-generic"); +addTest("testrunc11/gcc-c11-generic-1"); +# TODO: these messages are not even checked? +addTestFail("testc11/gcc-c11-generic-2-1", "Multiple defaults in generic"); +# addTestFail("testc11/gcc-c11-generic-2-2", "TODO"); +# addTestFail("testc11/gcc-c11-generic-2-3", "TODO"); +# addTestFail("testc11/gcc-c11-generic-2-4", "TODO"); +# addTestFail("testc11/gcc-c11-generic-2-5", "TODO"); +# addTestFail("testc11/gcc-c11-generic-2-6", "TODO"); +addTestFail("testc11/gcc-c11-generic-2-7", "No compatible associations or default in generic"); +addTest("testc11/gcc-c11-generic-3-1"); +addTestFail("testc11/gcc-c11-generic-3-2", "No compatible associations or default in generic"); +addTestFail("testc11/gcc-c11-generic-3-3", "No compatible associations or default in generic"); +addTestFail("testc11/gcc-c11-generic-3-4", "No compatible associations or default in generic"); +addTestFail("testc11/clang-c11-generic-1-1", "Multiple compatible associations in generic"); +addTestFail("testc11/clang-c11-generic-1-2", "No compatible associations or default in generic"); +addTest("testc11/clang-c11-generic-2"); # ---------------- c-torture ------------- ## if we have the c-torture tests add them