diff clang/lib/Parse/ParseCbC.cpp @ 152:e8a9b4f4d755

pull from 146
author anatofuz
date Wed, 11 Mar 2020 18:29:16 +0900
parents tools/clang/lib/Parse/ParseCbC.cpp@53f12981605a
children 70c77e05b61e
line wrap: on
line diff
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/clang/lib/Parse/ParseCbC.cpp	Wed Mar 11 18:29:16 2020 +0900
@@ -0,0 +1,1059 @@
+#ifndef noCbC
+
+#include "clang/Parse/Parser.h"
+#include "clang/Parse/RAIIObjectsForParser.h"
+#include "clang/AST/ASTContext.h"
+#include "clang/Basic/PrettyStackTrace.h"
+#include "clang/Basic/TargetInfo.h"
+#include "clang/Sema/DeclSpec.h"
+#include "clang/Sema/PrettyDeclStackTrace.h"
+#include "clang/Sema/Scope.h"
+#include "clang/Sema/Lookup.h"
+#include "clang/Lex/LiteralSupport.h"
+#include "clang/AST/ASTConsumer.h"
+#include "clang/Sema/SemaDiagnostic.h"
+
+#include <sstream>
+#include <string>
+#include "CbCHelper.h"
+
+using namespace clang;
+
+/// The class which belong to this namespace is from other files' namespace.
+/// Because those namespaces are unnamed namespaces, we can't access them.
+/// So create this namespace and copy classes from those namespaces.
+namespace ExternalSpace { // from ParseExpr.cpp , ParseStmt.cpp
+  class CastExpressionIdValidator : public CorrectionCandidateCallback {
+  public:
+    CastExpressionIdValidator(bool AllowTypes, bool AllowNonTypes)
+      : AllowNonTypes(AllowNonTypes) {
+      WantTypeSpecifiers = AllowTypes;
+    }
+
+    virtual bool ValidateCandidate(const TypoCorrection &candidate) {
+      NamedDecl *ND = candidate.getCorrectionDecl();
+      if (!ND)
+        return candidate.isKeyword();
+
+      if (isa<TypeDecl>(ND))
+        return WantTypeSpecifiers;
+      return AllowNonTypes;
+    }
+
+  private:
+    bool AllowNonTypes;
+  };
+
+  class StatementFilterCCC : public CorrectionCandidateCallback {
+  public:
+    StatementFilterCCC(Token nextTok) : NextToken(nextTok) {
+      WantTypeSpecifiers = nextTok.is(tok::l_paren) || nextTok.is(tok::less) ||
+        nextTok.is(tok::identifier) || nextTok.is(tok::star) ||
+        nextTok.is(tok::amp) || nextTok.is(tok::l_square);
+      WantExpressionKeywords = nextTok.is(tok::l_paren) ||
+        nextTok.is(tok::identifier) ||
+        nextTok.is(tok::arrow) || nextTok.is(tok::period);
+      WantRemainingKeywords = nextTok.is(tok::l_paren) || nextTok.is(tok::semi) ||
+        nextTok.is(tok::identifier) ||
+        nextTok.is(tok::l_brace);
+      WantCXXNamedCasts = false;
+    }
+
+    virtual bool ValidateCandidate(const TypoCorrection &candidate) {
+      if (FieldDecl *FD = candidate.getCorrectionDeclAs<FieldDecl>())
+        return !candidate.getCorrectionSpecifier() || isa<ObjCIvarDecl>(FD);
+      if (NextToken.is(tok::equal))
+        return candidate.getCorrectionDeclAs<VarDecl>();
+      if (NextToken.is(tok::period) &&
+          candidate.getCorrectionDeclAs<NamespaceDecl>())
+        return false;
+      return CorrectionCandidateCallback::ValidateCandidate(candidate);
+    }
+
+  private:
+    Token NextToken;
+  };
+}
+
+
+/// Prepare__retForGotoWithTheEnvExpr - Prepare __CbC_return, code segment for returning and some necessary statements.
+/// It is called when the parser find __return and statements are put into complex statement.
+/// 
+/// examples which are created:
+///   complex statement:
+///         ({
+///           __code (*__CbC_return)(return_type, void*);
+///           __CbC_return = code_segment_for_return;
+///           __CbC_return;
+///         });
+///   code segment:
+///         __code ret(return_type retval, void *env){
+///           *(return_type)((struct __CbC_env *)(env))->ret_p = retval;
+///             longjmp((int*)(((struct __CbC_env *)env)->env),1);
+///         }
+ExprResult Parser::Prepare__retForGotoWithTheEnvExpr(){
+
+  if (isVoidFunction()) { // error check : function type is void or not.
+    unsigned DiagID = Diags.getCustomDiagID(DiagnosticsEngine::Error, "continuation with the environment cannot use in the void function");
+    Diag(Tok, DiagID);
+    return ExprError();
+  }
+
+  StmtResult innerRes;
+  SourceLocation Loc = Tok.getLocation();
+  IdentifierInfo *__CbC_retII = CreateIdentifierInfo(__CBC_RETURN_NAME, Loc);
+  IdentifierInfo *retcsII = CreateUniqueIdentifierInfo(__CBC_RET_CODE_BASE_NAME, Loc);
+  Create__CbC_envStruct(Loc, AS_none);
+
+  Actions.ActOnStartStmtExpr();
+  StmtResult CompoundStmtRes;
+  ParseScope CompoundScope(this, Scope::DeclScope);
+  PrettyStackTraceLoc CrashInfo(PP.getSourceManager(),Loc,"in compound statement ('{}')");
+  StmtVector CompoundStmts; 
+
+  // create code segment for return to C's function
+  CreateRetCS(retcsII);
+    
+  // __code (*__CbC_return)();
+  innerRes = CreateDeclStmt(__CbC_retII, true, false, DeclSpec::TST___code);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  // __CbC_return = ret;
+  innerRes = CreateAssignmentStmt(__CbC_retII, retcsII);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  // __CbC_return;
+  innerRes = CreateComplexStmtRet(__CbC_retII, false);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  CompoundStmtRes = Actions.ActOnCompoundStmt(Loc,Loc,CompoundStmts,true);
+  ConsumeToken(); // eat the '__return'.
+  return Actions.ActOnStmtExpr(Loc, CompoundStmtRes.get(), Loc);
+}
+
+/// Prepare__envForGotoWithTheEnvExpr - Prepare __CbC_environment, struct __CbC_env and some necessary statements.
+/// It is called when the parser find __environment and statements are put into complex statement.
+/// 
+/// examples which are created:
+///   complex statement:
+///         ({
+///           volatile struct __CbC_env __CbC_environment;
+///           jmp_buf env_buf;
+///           return_type retval;
+///           __CbC_environment.ret_p = &retval;
+///           __CbC_environment.env = &env_buf;
+///           if (setjmp(__CbC_environment.env)){
+///             return retval;
+///           }
+///           &__CbC_environment;
+///         });
+///   struct __CbC_env:
+///         struct __CbC_env{
+///           void *ret_p,*env;
+///         }
+ExprResult Parser::Prepare__envForGotoWithTheEnvExpr(){
+
+  if (isVoidFunction()) { // error check : function type is void or not.
+    unsigned DiagID = Diags.getCustomDiagID(DiagnosticsEngine::Error, "continuation with the environment cannot use in the void function");
+    Diag(Tok, DiagID);
+    return ExprError();
+  }
+
+  StmtResult innerRes;
+  SourceLocation Loc = Tok.getLocation();
+  IdentifierInfo *bufII = CreateIdentifierInfo(__CBC_BUF_NAME, Loc);
+  IdentifierInfo *retvalII = CreateIdentifierInfo(__CBC_RETVAL_NAME, Loc);
+  IdentifierInfo *structII = CreateIdentifierInfo(__CBC_STRUCT_NAME, Loc);
+  IdentifierInfo *__CbC_envII = CreateIdentifierInfo(__CBC_ENVIRONMENT_NAME, Loc);
+  IdentifierInfo *envII = CreateIdentifierInfo(__CBC_STRUCT_ENV_NAME, Loc);
+  IdentifierInfo *ret_pII = CreateIdentifierInfo(__CBC_STRUCT_POINTER_NAME, Loc);
+  Create__CbC_envStruct(Loc, AS_none);
+  Actions.ActOnStartStmtExpr();
+  ParseScope CompoundScope(this, Scope::DeclScope);
+  PrettyStackTraceLoc CrashInfo(PP.getSourceManager(),Loc,"in compound statement ('{}')");
+  StmtVector CompoundStmts; 
+  ExprResult Result(true);
+  
+ // struct __CbC_env __CbC_environment;
+  innerRes = CreateDeclStmt(__CbC_envII, false, false, DeclSpec::TST_struct, structII, DeclSpec::TQ_volatile);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  // returnType retval;
+  innerRes = CreateDeclStmt(retvalII, false, true);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  // jmp_buf env_buf;
+  innerRes = CreateDeclStmt(bufII, false, false, DeclSpec::TST_typename, CreateIdentifierInfo("jmp_buf", Loc));
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  // __CbC_environment.ret_p = &retval;
+  innerRes = CreateAssignmentStmt(__CbC_envII, retvalII, true, true, ret_pII);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  // __CbC_environment.env = env_buf;
+  innerRes = CreateAssignmentStmt(__CbC_envII, bufII, true, false, envII);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  // create statements of setjmp
+  innerRes = CreateSjForContinuationWithTheEnv();
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+  
+  // __CbC_environment;
+  innerRes = CreateComplexStmtRet(__CbC_envII, true);
+  if (innerRes.isUsable())
+    CompoundStmts.push_back(innerRes.get());
+
+  StmtResult CompoundStmtRes = Actions.ActOnCompoundStmt(Loc,Loc,CompoundStmts,true);
+  ConsumeToken(); // eat the '__environment'.
+  Result =  Actions.ActOnStmtExpr(Loc, CompoundStmtRes.get(), Loc);
+
+  // cast 
+  ParsedType CastTy;
+  DeclSpec void_DS(AttrFactory);
+  setTST(&void_DS, DeclSpec::TST_void);
+  Declarator DeclaratorInfo(void_DS, DeclaratorContext::TypeNameContext);
+  DeclSpec star_DS(AttrFactory);
+  star_DS.Finish(Actions, Actions.getASTContext().getPrintingPolicy());
+  DeclaratorInfo.ExtendWithDeclSpec(star_DS);
+  DeclaratorInfo.SetIdentifier(nullptr, Tok.getLocation());
+  DeclaratorInfo.AddTypeInfo(DeclaratorChunk::getPointer(star_DS.getTypeQualifiers(), Loc,star_DS.getConstSpecLoc(),star_DS.getVolatileSpecLoc(),
+                                                         star_DS.getRestrictSpecLoc(),star_DS.getAtomicSpecLoc(),star_DS.getUnalignedSpecLoc()),star_DS.getAttributes(),SourceLocation());
+  return Actions.ActOnCastExpr(getCurScope(), Loc, DeclaratorInfo, CastTy,Loc, Result.get());
+  
+}
+
+/// CreateAssignmentStmt - Create assignment statement such as "aaa = bbb;", "auaua = llll;", etc.
+/// It can create 4 kinds of statement.
+/// 1. common assignment statement:
+///         variable '=' variable ';'
+/// 2. LHS variable is member of struct:
+///         structVar '.' member '=' variable ';'
+/// 3. RHS variable is address of operand:
+///         variable '=' '&' variable ';'
+/// 4. 2+3:
+///         structVar '.' member '=' '&' variable ';'
+StmtResult Parser::CreateAssignmentStmt(IdentifierInfo* LHSII, IdentifierInfo* RHSII, bool LHSisMemberAccess, bool RHShasAmp,
+                                        IdentifierInfo* extraLHSII, IdentifierInfo* extraRHSII){
+  ExprResult Expr,LHS,RHS;
+  
+  Token Next,LHSToken;
+  SourceLocation Loc = Tok.getLocation();
+  CXXScopeSpec SS;
+  Next.startToken();
+  Next.setKind(tok::period);
+  LHSToken.startToken();
+  LHSToken.setLocation(Loc);
+  LHSToken.setIdentifierInfo(LHSII);
+  LHSToken.setKind(tok::annot_primary_expr);
+  std::unique_ptr<ExternalSpace::StatementFilterCCC> Validator(new ExternalSpace::StatementFilterCCC(Next));
+  Sema::NameClassification Classification = Actions.ClassifyName(getCurScope(), SS, LHSII, Loc, Next, false, SS.isEmpty() ? std::move(Validator) : 0);
+  setExprAnnotation(LHSToken, Classification.getExpression());
+  LHSToken.setAnnotationEndLoc(Loc);
+  PP.AnnotateCachedTokens(LHSToken);
+  
+  LHS = getExprAnnotation(LHSToken);
+
+  if (LHSisMemberAccess) 
+    LHS = LookupMemberAndBuildExpr(extraLHSII, LHS.get(), false);
+  
+  RHS = LookupNameAndBuildExpr(RHSII);
+  if (RHShasAmp)
+    RHS = Actions.ActOnUnaryOp(getCurScope(), Loc, tok::amp, RHS.get());
+
+  Expr = Actions.ActOnBinOp(getCurScope(), Loc,tok::equal,LHS.get(),RHS.get());
+  
+  return Actions.ActOnExprStmt(Expr);
+}
+
+/// CreateDeclStmt - Create declaration statement such as "int aaa;".
+/// If isRetCS is true, create code segment for return to C's function. And Name is name of code segment.
+/// If copyType is true, type of variable is copied from callee.
+StmtResult Parser::CreateDeclStmt(IdentifierInfo *II, bool isRetCS, bool copyType, DeclSpec::TST valueType, IdentifierInfo* Name, DeclSpec::TQ TQ){
+  const PrintingPolicy &Policy = Actions.getASTContext().getPrintingPolicy();
+  SourceLocation Loc = Tok.getLocation();
+  DeclGroupPtrTy DeclGPT;
+  ParsingDeclSpec DS(*this);
+  DeclSpec *DSp;
+  DSp = &DS;
+
+  setTST(&DS, valueType, Name, TQ);
+  ParsingDeclarator D(*this, DS, static_cast<DeclaratorContext>(DeclaratorContext::BlockContext));
+  D.SetIdentifier(II, Loc);
+    
+  if (isRetCS) {
+    D.setEllipsisLoc(SourceLocation());
+    bool hadGroupingParens = D.hasGroupingParens();
+    D.setGroupingParens(true);
+    D.SetRangeEnd(Loc);
+    DeclSpec FDS(AttrFactory);
+    DS.Finish(Actions, Policy);
+    
+    D.AddTypeInfo(DeclaratorChunk::getPointer(FDS.getTypeQualifiers(), Loc, FDS.getConstSpecLoc(), FDS.getVolatileSpecLoc(),
+                                              FDS.getRestrictSpecLoc(), DS.getAtomicSpecLoc(), FDS.getUnalignedSpecLoc()), FDS.getAttributes(), SourceLocation());
+    D.setGroupingParens(hadGroupingParens);
+    
+    
+    ParseScope PrototypeScope(this,Scope::FunctionPrototypeScope|Scope::DeclScope|
+                              (D.isFunctionDeclaratorAFunctionDeclaration() ? Scope::FunctionDeclarationScope : 0));
+    bool HasProto = false;
+    SmallVector<DeclaratorChunk::ParamInfo, 16> ParamInfo;
+    SourceLocation EllipsisLoc, RefQualifierLoc, ConstQualifierLoc, VolatileQualifierLoc, RestrictQualifierLoc;
+    DeclSpec FPDS(AttrFactory);
+    bool RefQualifierIsLValueRef = true;
+    ExceptionSpecificationType ESpecType = EST_None;
+    SourceRange ESpecRange;
+    SmallVector<ParsedType, 2> DynamicExceptions;
+    SmallVector<SourceRange, 2> DynamicExceptionRanges;
+    ExprResult NoexceptExpr;
+    CachedTokens *ExceptionSpecTokens = 0;
+    ParsedAttributes FnAttrs(AttrFactory);
+    TypeResult TrailingReturnType;
+
+    ParmVarDecl *Param;
+    FunctionDecl *CurFunctionDecl = Actions.getCurFunctionDecl();
+    QualType CurFuncResQT = CurFunctionDecl->getReturnType();
+    TypeSourceInfo *CurFuncTI = Actions.Context.CreateTypeSourceInfo(CurFuncResQT);
+    
+    Param = CreateParam();
+    Param->setTypeSourceInfo(CurFuncTI);
+    Param->setType(CurFuncResQT);
+    ParamInfo.push_back(DeclaratorChunk::ParamInfo(0, Loc, Param, 0));
+    Param = CreateParam(0, 1, DeclSpec::TST_void);
+    ParamInfo.push_back(DeclaratorChunk::ParamInfo(0, Loc, Param, 0));
+    HasProto = true;
+    
+    D.AddTypeInfo(DeclaratorChunk::getFunction(HasProto, false, Loc, ParamInfo.data(),
+                                               ParamInfo.size(), EllipsisLoc, Loc, FPDS.getTypeQualifiers(),
+                                               RefQualifierIsLValueRef, RefQualifierLoc, ConstQualifierLoc,
+                                               VolatileQualifierLoc, RefQualifierLoc, SourceLocation(),
+                                               ESpecType, ESpecRange.getBegin(),
+                                               DynamicExceptions.data(), DynamicExceptionRanges.data(),
+                                               DynamicExceptions.size(),
+                                               NoexceptExpr.isUsable() ? NoexceptExpr.get() : 0, ExceptionSpecTokens, None, Loc, Loc, D, TrailingReturnType),
+                  FnAttrs, Loc);
+    PrototypeScope.Exit();
+    DSp = &FDS;
+  }
+  
+  SmallVector<Decl *, 8> DeclsInGroup;
+  Decl *FirstDecl;
+  
+  if (copyType)
+    FirstDecl = HandleDeclAndChangeDeclType(D);
+  else
+    FirstDecl = ParseDeclarationAfterDeclaratorAndAttributes(D);
+  
+  D.complete(FirstDecl);
+  DeclsInGroup.push_back(FirstDecl);
+  DeclGPT =  Actions.FinalizeDeclaratorGroup(getCurScope(), *DSp, DeclsInGroup);
+  return Actions.ActOnDeclStmt(DeclGPT, Loc, Loc);
+}
+
+
+/// handleDeclAndChangeDeclType - This function imitated Parser::ParseDeclarationAfterDeclaratorAndAttributes() and Sema::ActOnDeclarator().
+/// The origins get Type from Declarator but this function get Type from current function.
+/// It is useful for CbC to create statements for the continuation with the environments.
+Decl* Parser::HandleDeclAndChangeDeclType(Declarator &D) {
+  D.setFunctionDefinitionKind(FDK_Declaration);
+  DeclarationNameInfo NameInfo = Actions.GetNameForDeclarator(D);
+  DeclContext *DC = Actions.CurContext;
+  QualType R = Actions.getCurFunctionDecl()->getReturnType(); // copy a type
+  TypeSourceInfo *TInfo = Actions.Context.CreateTypeSourceInfo(R); // copy a type infomation
+  Scope *S = getCurScope();
+  LookupResult Previous(Actions, NameInfo, Actions.LookupOrdinaryName, Actions.ForVisibleRedeclaration);
+  bool IsLinkageLookup = false;
+  bool CreateBuiltins = false;
+  
+  // If the declaration we're planning to build will be a function
+  // or object with linkage, then look for another declaration with
+  // linkage (C99 6.2.2p4-5 and C++ [basic.link]p6).
+  //
+  // If the declaration we're planning to build will be declared with
+  // external linkage in the translation unit, create any builtin with
+  // the same name.
+  if (R->isFunctionType()) {
+    IsLinkageLookup = true;
+    CreateBuiltins =
+      Actions.CurContext->getEnclosingNamespaceContext()->isTranslationUnit();
+  } else if (Actions.CurContext->getRedeclContext()->isTranslationUnit())
+    CreateBuiltins = true;
+  
+  if (IsLinkageLookup)
+    Previous.clear(Actions.LookupRedeclarationWithLinkage);
+  
+  Actions.LookupName(Previous, S, CreateBuiltins);
+
+  // In C++, the previous declaration we find might be a tag type
+  // (class or enum). In this case, the new declaration will hide the
+  // tag type. Note that this does does not apply if we're declaring a
+  // typedef (C++ [dcl.typedef]p4).
+  if (Previous.isSingleTagDecl())
+    Previous.clear();
+  NamedDecl *New;
+  bool AddToScope = true;
+  if (R->isFunctionType()) {
+    New = Actions.ActOnFunctionDeclarator(S, D, DC, TInfo, Previous,
+                                          MultiTemplateParamsArg(), AddToScope);
+  } else {
+    New = Actions.ActOnVariableDeclarator(S, D, DC, TInfo, Previous,
+                                          MultiTemplateParamsArg(), AddToScope);
+  }
+  
+  if (New->getDeclName() && AddToScope) {
+    // Only make a locally-scoped extern declaration visible if it is the first
+    // declaration of this entity. Qualified lookup for such an entity should
+    // only find this declaration if there is no visible declaration of it.
+    bool AddToContext = !D.isRedeclaration() || !New->isLocalExternDecl();
+    Actions.PushOnScopeChains(New, S, AddToContext);
+    if (!AddToContext)
+      Actions.CurContext->addHiddenDecl(New);
+  }
+  
+  return New;
+}
+
+/// CreateSjForContinuationWithEnv - Create statements of setjmp for continuation with the environment.
+///   code example:
+///         if (setjmp(__CbC_environment.env)){
+///           return retval;
+///         }
+StmtResult Parser::CreateSjForContinuationWithTheEnv(){
+  SourceLocation Loc = Tok.getLocation();
+  StmtResult IfRes;
+  ParseScope IfScope(this, Scope::DeclScope | Scope::ControlScope, true/* C99 or CXX */);
+  ExprResult CondExp;
+  StmtResult InitStmt;
+  Sema::ConditionResult Cond;
+
+  CondExp = LookupNameAndBuildExpr(CreateIdentifierInfo("__builtin_setjmp", Loc));
+  ExprVector ArgExprs;
+  ExprResult __envExprRes = CondExp.get();
+
+  __envExprRes = LookupNameAndBuildExpr(CreateIdentifierInfo(__CBC_ENVIRONMENT_NAME, Loc));
+  __envExprRes = LookupMemberAndBuildExpr(CreateIdentifierInfo(__CBC_STRUCT_ENV_NAME, Loc), __envExprRes.get(), false);
+
+  ArgExprs.push_back(__envExprRes.get());
+  CondExp = Actions.ActOnCallExpr(getCurScope(), CondExp.get(), Loc, ArgExprs, Loc, 0);
+  Cond    = Actions.ActOnCondition(getCurScope(), Loc, CondExp.get(), Sema::ConditionKind::Boolean);
+
+
+  ParseScope InnerScope(this, Scope::DeclScope,false);
+  SourceLocation InnerStatementTrailingElseLoc;
+    
+  StmtResult StmtRes;
+  ParseScope CompoundScope(this, Scope::DeclScope);
+  PrettyStackTraceLoc CrashInfo(PP.getSourceManager(),Loc,"in create setjmp statement for CbC");
+  StmtVector innerStmts;
+  StmtResult innerStmtRes;
+  ExprResult innerExprRes;
+  innerExprRes = LookupNameAndBuildExpr(CreateIdentifierInfo(__CBC_RETVAL_NAME, Loc));
+  innerStmtRes = Actions.ActOnReturnStmt(Loc, innerExprRes.get(), getCurScope());
+  if (innerStmtRes.isUsable())
+    innerStmts.push_back(innerStmtRes.get());
+  StmtRes = Actions.ActOnCompoundStmt(Loc, Loc,innerStmts, false);
+  StmtResult ThenStmt(StmtRes);
+  InnerScope.Exit();
+  IfScope.Exit();
+  StmtResult ElseStmt;
+  IfRes = Actions.ActOnIfStmt(Loc, false, CondExp.get(), Cond, ThenStmt.get(),Loc, ElseStmt.get());
+  return IfRes;
+}
+
+
+/// LookupNameAndBuildExpr - Look up name, create ExprResult and return it.
+ExprResult Parser::LookupNameAndBuildExpr(IdentifierInfo *II, bool IsAddressOfOperand){
+  SourceLocation Loc = Tok.getLocation();
+  UnqualifiedId Name;
+  CXXScopeSpec SS;
+  SourceLocation TemplateKWLoc;
+  std::unique_ptr<ExternalSpace::CastExpressionIdValidator> Validator(new ExternalSpace::CastExpressionIdValidator(false,true));
+  Name.setIdentifier(II, Loc);
+  return Actions.ActOnIdExpression(getCurScope(), SS, TemplateKWLoc, Name, false, IsAddressOfOperand, std::move(Validator));
+}
+
+/// LookupMemberAndBuildExpr - Look up member name, create ExprResult and return it.
+/// If IsArrow is true, the name is accessed by arrow operand.
+ExprResult Parser::LookupMemberAndBuildExpr(IdentifierInfo *II, Expr* Base, bool IsArrow){
+  SourceLocation Loc = Tok.getLocation();
+  CXXScopeSpec SS;
+  UnqualifiedId Name;
+  SourceLocation TemplateKWLoc;
+  tok::TokenKind OpKind = (IsArrow ? tok::arrow : tok::period);
+  Name.setIdentifier(II,Loc);
+  return Actions.ActOnMemberAccessExpr(getCurScope(), Base, Loc, OpKind, SS, TemplateKWLoc, Name, nullptr);
+}
+
+
+/// Create__CbC_envStruct - This method create "struct __CbC_env" which is used to continuation with environment.
+/// If the __CbC_env has been already defined, it doesn't create __CbC_env again.
+///   The example of struct which is created :
+///        struct __CbC_env{
+///          void *ret_p,*env;
+///        };
+void Parser::Create__CbC_envStruct(SourceLocation Loc, AccessSpecifier AS) {
+
+  IdentifierInfo *Name = CreateIdentifierInfo(__CBC_STRUCT_NAME, Loc);
+  // Check previous definition. If the __CbC_env has been already defined, we have not to create again.
+  LookupResult Previous(Actions, Name, Loc, Actions.LookupTagName, Actions.ForVisibleRedeclaration);
+  if(Actions.LookupName(Previous, getCurScope()))
+    return;
+
+  Scope *SavedScope = getCurScope();
+  DeclContext *SavedContext = Actions.CurContext;
+  sema::FunctionScopeInfo *SavedFSI = Actions.FunctionScopes.pop_back_val();
+
+  Actions.CurContext = static_cast<DeclContext *>(Actions.Context.getTranslationUnitDecl());
+  Scope *TopScope = getCurScope();
+  while(TopScope->getParent() != NULL)
+    TopScope = TopScope->getParent();
+  Actions.CurScope = TopScope;
+
+  ParsingDeclSpec SDS(*this);
+  SDS.SetRangeStart(Loc);
+  SDS.SetRangeEnd(Loc);
+  DeclSpec::TST TagType = DeclSpec::TST_struct;
+  DeclResult TagOrTempResult = true;
+  bool Owned = false;
+  bool IsDependent = false;
+  ParsedAttributesWithRange attrs(AttrFactory);
+  MultiTemplateParamsArg TParams;
+      
+  TagOrTempResult = Actions.ActOnTag(getCurScope(), TagType, Sema::TUK_Definition, Loc,
+                                     SDS.getTypeSpecScope(), Name, Loc, attrs.getList(), AS,
+                                     SDS.getModulePrivateSpecLoc(), TParams, Owned, IsDependent,
+                                     SourceLocation(), false, clang::TypeResult(), false, false);
+
+  Decl *TagDecl = TagOrTempResult.get();
+  PrettyDeclStackTraceEntry CrashInfo(Actions, TagDecl, Loc, "parsing struct/union body");
+  ParseScope StructScope(this, Scope::ClassScope|Scope::DeclScope);
+  Actions.ActOnTagStartDefinition(getCurScope(), TagDecl);
+  SmallVector<Decl *, 32> FieldDecls;
+
+  FieldDecls.push_back(Create__CbC_envBody(TagDecl, DeclSpec::TST_void, Loc, __CBC_STRUCT_POINTER_NAME));
+  FieldDecls.push_back(Create__CbC_envBody(TagDecl, DeclSpec::TST_void, Loc, __CBC_STRUCT_ENV_NAME));
+
+  Actions.ActOnFields(getCurScope(),Loc, TagDecl, FieldDecls,Loc, Loc,attrs.getList());
+  StructScope.Exit();
+  Actions.ActOnTagFinishDefinition(getCurScope(), TagDecl, Loc);
+
+  Actions.CurScope = SavedScope;
+  Actions.CurContext = SavedContext;
+  Actions.FunctionScopes.push_back(SavedFSI);
+}
+
+/// Create__CbC_envBody - Create void type pointer ret_p and env which are member of __CbC_env.
+Decl* Parser::Create__CbC_envBody(Decl* TagDecl, DeclSpec::TST T, SourceLocation Loc, const char* Name){
+  const PrintingPolicy &Policy = Actions.getASTContext().getPrintingPolicy();
+  ParsingDeclSpec PDS(*this);
+  setTST(&PDS, T);
+  SourceLocation CommaLoc;
+  ParsingFieldDeclarator DeclaratorInfo(*this, PDS);
+  DeclaratorInfo.D.setCommaLoc(CommaLoc);
+  DeclaratorInfo.D.SetRangeEnd(Loc);
+  DeclSpec DS(AttrFactory);
+  DS.Finish(Actions, Policy);
+  DeclaratorInfo.D.SetIdentifier(CreateIdentifierInfo(Name, Loc),Loc);
+
+  DeclaratorInfo.D.AddTypeInfo(DeclaratorChunk::getPointer(DS.getTypeQualifiers(), Loc,DS.getConstSpecLoc(),
+                                                           DS.getVolatileSpecLoc(),DS.getRestrictSpecLoc(), DS.getAtomicSpecLoc(), DS.getUnalignedSpecLoc()),
+                               DS.getAttributes(),SourceLocation());
+  Decl *Field = Actions.ActOnField(getCurScope(), TagDecl,
+                                   DeclaratorInfo.D.getDeclSpec().getSourceRange().getBegin(),
+                                   DeclaratorInfo.D, DeclaratorInfo.BitfieldSize);
+  DeclaratorInfo.complete(Field);
+  return Field;
+}
+
+/// CreateIdentifierInfo - Create IdentifierInfo from char pointer.
+///   usage : 
+///          IdentifierInfo *II = CreateIdentifierInfo(IIName, Location);
+IdentifierInfo* Parser::CreateIdentifierInfo(const char* Name, SourceLocation Loc) {
+  int length = strlen(Name);
+  Token TokenForII;
+  TokenForII.startToken();
+  TokenForII.setLocation(Loc);
+  TokenForII.setLength(length);
+  TokenForII.setKind(tok::raw_identifier);
+  TokenForII.setRawIdentifierData(Name);
+  IdentifierInfo *II;
+  II = PP.getIdentifierInfo(TokenForII.getRawIdentifier());
+  TokenForII.setIdentifierInfo(II);
+  TokenForII.setKind(II->getTokenID());
+  return II;
+}
+
+/// CreateUniqueIdentifierInfo - Create unique IdentifierInfo.
+/// IdentifierInfos have unique name which were created by this function.
+/// Naming conventions : 
+///   current 'function name' '..' 'variable name' 'uniqueID'
+/// For example, if current function's name is 'main' and variable name is 'auaua', IdentifierInfo's name is 'main..auaua'.
+IdentifierInfo* Parser::CreateUniqueIdentifierInfo(const char* Name, SourceLocation Loc){
+  IdentifierInfo *II;
+  std::ostringstream os;
+  
+  os << curFuncName << ".." /* separator */ << Name << UniqueId;
+  II = CreateIdentifierInfo(os.str().c_str(), Loc);
+  UniqueId++; // Modify the unique ID.
+  return II;
+}
+
+
+/// CreateRetCS - Create code segment which is used for continuation with the environment.
+///   create these codes:
+///         __code ret(return_type retval, void *env){
+///           *(return_type)((struct CbC_environment *)(env))->ret_p = n;
+///             longjmp((void*)(((struct __CbC_environment *)env)->env),1);
+///         }
+void Parser::CreateRetCS(IdentifierInfo *csName){
+  const PrintingPolicy &Policy = Actions.getASTContext().getPrintingPolicy();
+  QualType CurFuncResQT = Actions.getCurFunctionDecl()->getReturnType();
+  
+  Scope *SavedScope = getCurScope();
+  DeclContext *SavedContext = Actions.CurContext;
+  TypeSourceInfo *CurFuncTI = Actions.Context.CreateTypeSourceInfo(CurFuncResQT);
+  sema::FunctionScopeInfo *SavedFSI = Actions.FunctionScopes.pop_back_val();
+
+  Actions.CurContext = static_cast<DeclContext *>(Actions.Context.getTranslationUnitDecl());
+  Scope *TopScope = getCurScope();
+  while(TopScope->getParent() != NULL)
+    TopScope = TopScope->getParent();
+  Actions.CurScope = TopScope;
+
+  DeclGroupPtrTy returnDecl = DeclGroupPtrTy();
+  SourceLocation Loc = Tok.getLocation();
+  ParsingDeclSpec PDS(*this);
+  setTST(&PDS, DeclSpec::TST___code);
+  ParsingDeclarator D(*this, PDS, static_cast<DeclaratorContext>(DeclaratorContext::FileContext));
+  D.SetIdentifier(csName, Loc);
+  ParseScope PrototypeScope(this,Scope::FunctionPrototypeScope|Scope::DeclScope|Scope::FunctionDeclarationScope);
+  bool IsAmbiguous = false;
+  bool HasProto = true;
+  SmallVector<DeclaratorChunk::ParamInfo, 16> ParamInfo;
+  SourceLocation EllipsisLoc, RefQualifierLoc, ConstQualifierLoc, VolatileQualifierLoc, RestrictQualifierLoc;
+  DeclSpec FDS(AttrFactory);
+  bool RefQualifierIsLValueRef = true;
+  ExceptionSpecificationType ESpecType = EST_None;
+  SourceRange ESpecRange;
+  SmallVector<ParsedType, 2> DynamicExceptions;
+  SmallVector<SourceRange, 2> DynamicExceptionRanges;
+  ExprResult NoexceptExpr;
+  CachedTokens *ExceptionSpecTokens = 0;
+  ParsedAttributes FnAttrs(AttrFactory);
+  TypeResult TrailingReturnType;
+  ParmVarDecl *Param;
+  
+  IdentifierInfo *retvalII = CreateIdentifierInfo(__CBC_RETVAL_NAME, Loc);
+  Param = CreateParam(retvalII);
+  Param->setTypeSourceInfo(CurFuncTI);
+  Param->setType(CurFuncResQT);
+
+  ParamInfo.push_back(DeclaratorChunk::ParamInfo(retvalII, Loc, Param, 0));
+  IdentifierInfo *envII = CreateIdentifierInfo(__CBC_STRUCT_ENV_NAME, Loc);
+  Param = CreateParam(envII, 1, DeclSpec::TST_void);
+  ParamInfo.push_back(DeclaratorChunk::ParamInfo(envII, Loc, Param, 0));
+
+  D.AddTypeInfo(DeclaratorChunk::getFunction(HasProto, IsAmbiguous, Loc, ParamInfo.data(), ParamInfo.size(), EllipsisLoc, Loc,
+                                             FDS.getTypeQualifiers(), RefQualifierIsLValueRef, RefQualifierLoc, ConstQualifierLoc,
+                                             VolatileQualifierLoc, RestrictQualifierLoc, SourceLocation(),
+                                             ESpecType, ESpecRange.getBegin(),
+                                             DynamicExceptions.data(), DynamicExceptionRanges.data(), DynamicExceptions.size(),
+                                             NoexceptExpr.isUsable() ? NoexceptExpr.get() : 0, ExceptionSpecTokens, None,
+                                             Loc, Loc, D, TrailingReturnType), FnAttrs, Loc);
+  PrototypeScope.Exit();
+  
+  Decl *TheDecl;
+  ParseScope BodyScope(this, Scope::FnScope|Scope::DeclScope);
+  Sema::SkipBodyInfo SkipBody;
+  const ParsedTemplateInfo &TemplateInfo = ParsedTemplateInfo();
+  Decl *BodyRes = Actions.ActOnStartOfFunctionDef(getCurScope(), D,
+                                                  TemplateInfo.TemplateParams ? *TemplateInfo.TemplateParams : MultiTemplateParamsArg(),
+                                                  &SkipBody);
+
+  D.complete(BodyRes);
+  D.getMutableDeclSpec().abort();
+  Actions.ActOnDefaultCtorInitializers(BodyRes);
+  StmtResult FnBody;
+  StmtVector FnStmts;
+  StmtResult innerR;
+  ExprResult retvalAssginmentExpr,LHS;
+  ExprVector ArgExprs;
+  CommaLocsTy CommaLocs;
+  DeclSpec envDS(AttrFactory);
+  IdentifierInfo *structName = CreateIdentifierInfo(__CBC_STRUCT_NAME, Loc);
+  setTST(&envDS, DeclSpec::TST_struct, structName);
+
+  Declarator envDInfo(envDS, DeclaratorContext::TypeNameContext);
+  envDInfo.SetRangeEnd(Loc);
+  DeclSpec starDS(AttrFactory);
+  starDS.Finish(Actions, Policy);
+  envDInfo.SetIdentifier(0,Loc);
+  envDInfo.AddTypeInfo(DeclaratorChunk::getPointer(starDS.getTypeQualifiers(), Loc,
+                                                   starDS.getConstSpecLoc(),
+                                                   starDS.getVolatileSpecLoc(),
+                                                   starDS.getRestrictSpecLoc(),
+                                                   starDS.getAtomicSpecLoc(),
+                                                   starDS.getUnalignedSpecLoc()),
+                       starDS.getAttributes(),
+                       SourceLocation());
+  ExprVector ArgExprs2;
+  LHS = LookupNameAndBuildExpr(envII);
+  ArgExprs2.push_back(LHS.get());
+  LHS = Actions.ActOnParenListExpr(Loc, Loc, ArgExprs2);
+  Expr *envCastExpr = LHS.get();
+  TypeSourceInfo *castTInfo = Actions.GetTypeForDeclaratorCast(envDInfo, envCastExpr->getType());
+  LHS = Actions.MaybeConvertParenListExprToParenExpr(getCurScope(), envCastExpr);
+  envCastExpr = LHS.get();
+  LHS = Actions.BuildCStyleCastExpr(Loc, castTInfo, Loc, envCastExpr);
+  ArgExprs.push_back(LHS.get());	
+  LHS = Actions.ActOnParenListExpr(Loc, Loc, ArgExprs);
+  LHS = LookupMemberAndBuildExpr(CreateIdentifierInfo(__CBC_STRUCT_POINTER_NAME, Loc),
+                                 LHS.get(), true);
+  Expr *ret_pCastExpr = LHS.get();
+  DeclarationName noValDeclName;
+  TypeSourceInfo *CurFuncTypesPointerTI = Actions.Context.CreateTypeSourceInfo(Actions.BuildPointerType(CurFuncResQT, Loc, noValDeclName));
+  LHS = Actions.BuildCStyleCastExpr(Loc, CurFuncTypesPointerTI, Loc, ret_pCastExpr);
+  LHS = Actions.ActOnUnaryOp(getCurScope(), Loc, tok::star, LHS.get());
+  ExprResult RHS;
+  RHS = LookupNameAndBuildExpr(retvalII);
+
+  retvalAssginmentExpr = Actions.ActOnBinOp(getCurScope(), Loc, tok::equal, LHS.get(), RHS.get());
+  innerR = Actions.ActOnExprStmt(retvalAssginmentExpr);
+  if(innerR.isUsable())
+    FnStmts.push_back(innerR.get());
+
+  ExprResult ljExpr,ljLHS;
+  ljExpr = IIToExpr(CreateIdentifierInfo("__builtin_longjmp", Loc), tok::l_paren);
+  ExprVector ljArgExprs;
+  DeclSpec ljDS(AttrFactory);
+  setTST(&ljDS, DeclSpec::TST_struct, structName);
+
+  Declarator ljD(ljDS, DeclaratorContext::TypeNameContext);
+  ljD.SetRangeEnd(Loc);
+  DeclSpec starDS2(AttrFactory);
+  starDS2.Finish(Actions, Policy);
+  ljD.ExtendWithDeclSpec(starDS2);
+  ljD.SetIdentifier(0, Loc);
+  ljD.AddTypeInfo(DeclaratorChunk::getPointer(ljDS.getTypeQualifiers(), Loc,
+                                              ljDS.getConstSpecLoc(),
+                                              ljDS.getVolatileSpecLoc(),
+                                              ljDS.getRestrictSpecLoc(),
+                                              ljDS.getAtomicSpecLoc(),
+                                              ljDS.getUnalignedSpecLoc()),
+                  ljDS.getAttributes(),
+                  SourceLocation());
+  ljLHS = LookupNameAndBuildExpr(envII);
+  Expr *ljCastExpr = ljLHS.get();
+  TypeSourceInfo *ljCastTInfo = Actions.GetTypeForDeclaratorCast(ljD, ljCastExpr->getType());
+  ljLHS = Actions.BuildCStyleCastExpr(Loc, ljCastTInfo, Loc, ljCastExpr);
+  ljLHS = Actions.ActOnParenExpr(Loc, Loc, ljLHS.get());
+  ljLHS = LookupMemberAndBuildExpr(envII, ljLHS.get(), true);
+  ljLHS = Actions.ActOnParenExpr(Loc, Loc, ljLHS.get());
+  ljArgExprs.push_back(ljLHS.get());
+  CommaLocs.push_back(Loc);
+  ljLHS = Actions.ActOnIntegerConstant(Loc, 1 /* return value for setjmp */);
+  ljArgExprs.push_back(ljLHS.get());
+  ljExpr = Actions.ActOnCallExpr(getCurScope(), ljExpr.get(), Loc, ljArgExprs, Loc, 0);
+  innerR = Actions.ActOnExprStmt(ljExpr);
+  if(innerR.isUsable())
+    FnStmts.push_back(innerR.get());
+  FnBody = Actions.ActOnCompoundStmt(Loc, Loc, FnStmts, false);
+  BodyScope.Exit();
+  TheDecl = Actions.ActOnFinishFunctionBody(BodyRes, FnBody.get());
+  returnDecl =  Actions.ConvertDeclToDeclGroup(TheDecl);
+  (&Actions.getASTConsumer())->HandleTopLevelDecl(returnDecl.get());
+  Actions.CurScope = SavedScope;
+  Actions.CurContext = SavedContext;
+  Actions.FunctionScopes.push_back(SavedFSI);
+}
+
+/// IIToExpr - Create ExprResult from IdentifierInfo. 
+/// It is used when II is a not primary expression such as not primary types, a function's name, etc.
+ExprResult Parser::IIToExpr(IdentifierInfo *II, tok::TokenKind Kind){
+  SourceLocation Loc = Tok.getLocation();
+  Token Next,IITok;
+  Next.setKind(Kind);
+  std::unique_ptr<ExternalSpace::StatementFilterCCC> CCCValidator(new ExternalSpace::StatementFilterCCC(Next));
+  CXXScopeSpec SS;
+  Sema::NameClassification Classification = Actions.ClassifyName(getCurScope(), SS, II, Loc, Next, false, std::move(CCCValidator));
+  IITok.startToken();
+  IITok.setLocation(Loc);
+  IITok.setIdentifierInfo(II);
+  IITok.setKind(tok::annot_primary_expr);
+  setExprAnnotation(IITok, Classification.getExpression());
+  IITok.setAnnotationEndLoc(Loc);
+  PP.AnnotateCachedTokens(IITok);
+  return getExprAnnotation(IITok);
+}
+
+/// CreateComplexStmtRet - Create return value for complex statements.
+///
+///   ({ /* some statements */
+///      return_value; )};
+///     ^^^^^^^^^^^^^ Create it.
+StmtResult Parser::CreateComplexStmtRet(IdentifierInfo *II, bool IsAddressOfOperand){
+  ExprResult ER;
+  if (IsAddressOfOperand) {
+    ER = LookupNameAndBuildExpr(II, true);
+    ER = Actions.ActOnUnaryOp(getCurScope(), Tok.getLocation(), tok::amp, ER.get());
+  }
+  else
+    ER = IIToExpr(II,tok::semi);
+  return Actions.ActOnExprStmt(ER);
+}
+
+/// CreateParam - Create paramator for functions.
+/// 
+/// int funcname(int aua) { 
+///              ^^^^^^^ Create it.
+ParmVarDecl* Parser::CreateParam(IdentifierInfo *II, int pointerNum, DeclSpec::TST T){
+  const PrintingPolicy &Policy = Actions.getASTContext().getPrintingPolicy();
+  SourceLocation Loc = Tok.getLocation();
+  DeclSpec DS(AttrFactory);
+  setTST(&DS, T);
+  Declarator ParamDeclarator(DS, DeclaratorContext::PrototypeContext);
+  ParamDeclarator.SetIdentifier(II, Loc);
+  for(int i = 0;i<pointerNum; i++){
+    DeclSpec pointerDS(AttrFactory);
+    pointerDS.Finish(Actions, Policy);
+    ParamDeclarator.AddTypeInfo(DeclaratorChunk::getPointer(pointerDS.getTypeQualifiers(), Loc,
+                                                            pointerDS.getConstSpecLoc(),
+                                                            pointerDS.getVolatileSpecLoc(),
+                                                            pointerDS.getRestrictSpecLoc(),
+                                                            pointerDS.getAtomicSpecLoc(),
+                                                            pointerDS.getUnalignedSpecLoc()),
+                                pointerDS.getAttributes(),SourceLocation());
+  }
+  ParmVarDecl *Param = dyn_cast<ParmVarDecl>(Actions.ActOnParamDeclarator(getCurScope(), ParamDeclarator));
+  return Param;
+
+}
+
+/// setTST - set TypeSpecifierType(TST) DeclSpec.
+/// TST is specifiers the kind of type such as int, double, char, etc.
+void Parser::setTST(DeclSpec *DS, DeclSpec::TST T, IdentifierInfo* Name, DeclSpec::TQ TQ){
+  const PrintingPolicy &Policy = Actions.getASTContext().getPrintingPolicy();
+  SourceLocation Loc = Tok.getLocation();
+  bool isInvalid = false;
+  const char *PrevSpec = 0;
+  unsigned DiagID = 0;
+  CXXScopeSpec SS;
+  DS->SetRangeStart(Loc);
+  DS->SetRangeEnd(Loc);
+  if (TQ != DeclSpec::TQ_unspecified) {
+    isInvalid = DS->SetTypeQual(DeclSpec::TQ_volatile, Loc, PrevSpec, DiagID,
+                               getLangOpts());
+  }
+
+  if (T == DeclSpec::TST_struct) {
+    ParsedAttributesWithRange attrs(AttrFactory);
+    DeclResult TagOrTempResult = true;
+    bool Owned = false;
+    bool IsDependent = false;
+    MultiTemplateParamsArg TParams;
+    TagOrTempResult = Actions.ActOnTag(getCurScope(), T, Sema::TUK_Reference, Loc,
+                                       SS, Name, Loc, attrs.getList(), AS_none,
+                                       DS->getModulePrivateSpecLoc(),
+                                       TParams, Owned, IsDependent,
+                                       SourceLocation(), false,
+                                       clang::TypeResult(), false, false);
+    isInvalid = DS->SetTypeSpecType(T, Loc, Loc, PrevSpec, DiagID, TagOrTempResult.get(), Owned, Policy);
+  }
+  else if (T == DeclSpec::TST_typename) {
+    Token Next,TypeTok;
+    Next.setKind(tok::identifier);
+    std::unique_ptr<ExternalSpace::StatementFilterCCC> CCCValidator(new ExternalSpace::StatementFilterCCC(Next));
+    Sema::NameClassification Classification = Actions.ClassifyName(getCurScope(), SS, Name, Loc, Next, false, std::move(CCCValidator));
+    TypeTok.startToken();
+    TypeTok.setLocation(Loc);
+    TypeTok.setIdentifierInfo(Name);
+    TypeTok.setKind(tok::annot_typename);
+    setTypeAnnotation(TypeTok, Classification.getType());
+    TypeTok.setAnnotationEndLoc(Loc);
+    PP.AnnotateCachedTokens(TypeTok);
+    if (TypeTok.getAnnotationValue()) {
+      ParsedType PT = getTypeAnnotation(TypeTok);
+      isInvalid = DS->SetTypeSpecType(T, Loc, PrevSpec, DiagID, PT, Policy);
+    } else
+      DS->SetTypeSpecError();
+  }
+  else
+    isInvalid = DS->SetTypeSpecType(T, Loc, PrevSpec, DiagID, Policy);
+  
+  DS->Finish(Actions, Policy);
+  if (isInvalid) {
+    assert(PrevSpec && "Method did not return previous specifier!");
+    assert(DiagID);
+    if (DiagID == diag::ext_duplicate_declspec)
+      Diag(Tok, DiagID)
+        << PrevSpec << FixItHint::CreateRemoval(Tok.getLocation());
+    else
+      Diag(Tok, DiagID) << PrevSpec;
+  }
+}
+
+/// CheckTheSjHeader - Check whether setjmp.h has been already included or not.
+/// If not, include it.
+void Parser::CheckTheSjHeader(){
+  SourceLocation Loc = Tok.getLocation();
+  LookupResult R(Actions, CreateIdentifierInfo("setjmp", Loc), Loc, Actions.LookupOrdinaryName, Actions.ForVisibleRedeclaration);
+  if (!Actions.LookupName(R, getCurScope())){ // look up the setjmp
+    if (PP.IncludeHeader(Tok, "setjmp.h"))
+      ConsumeToken();
+  }
+}
+
+/// isVoidFunction - Return true if current function return type is void.
+bool Parser::isVoidFunction(){
+  return Actions.getCurFunctionDecl()->getReturnType().getTypePtr()->isVoidType();
+}
+
+/// ParseCbCGotoStatement
+///       jump-statement:
+/// [CbC]   'goto' codeSegment ';'
+///
+StmtResult Parser::ParseCbCGotoStatement(ParsedAttributesWithRange &Attrs,StmtVector &Stmts) {
+  assert(Tok.is(tok::kw_goto) && "Not a goto stmt!");
+  ParseScope CompoundScope(this, Scope::DeclScope);
+  StmtVector CompoundedStmts;
+
+  SourceLocation gotoLoc = ConsumeToken();  // eat the 'goto'.
+  StmtResult gotoRes;
+  Token TokAfterGoto = Tok;
+  Stmtsp = &Stmts;
+  
+  gotoRes = ParseStatementOrDeclaration(Stmts, ACK_Any);
+
+  if (gotoRes.get() == NULL)
+    return StmtError();
+  else if (gotoRes.get()->getStmtClass() != Stmt::CallExprClass) { // if it is not function call
+    unsigned DiagID = Diags.getCustomDiagID(DiagnosticsEngine::Error, "expected identifier or codesegment call");
+    Diag(TokAfterGoto, DiagID);
+    return StmtError();
+  }
+  
+  assert((Attrs.empty() || gotoRes.isInvalid() || gotoRes.isUsable()) &&
+         "attributes on empty statement");
+  if (!(Attrs.empty() || gotoRes.isInvalid()))
+    gotoRes = Actions.ProcessStmtAttributes(gotoRes.get(), Attrs.getList(), Attrs.Range);
+  if (gotoRes.isUsable())
+    CompoundedStmts.push_back(gotoRes.get());
+
+  // add return; after goto codesegment();
+  if (Actions.getCurFunctionDecl()->getReturnType().getTypePtr()->is__CodeType()) {
+    ExprResult retExpr;
+    StmtResult retRes;
+    retRes = Actions.ActOnReturnStmt(gotoLoc, retExpr.get(), getCurScope());
+    if (retRes.isUsable())
+      CompoundedStmts.push_back(retRes.get());
+  }
+  return Actions.ActOnCompoundStmt(gotoLoc, Tok.getLocation(), CompoundedStmts, false);
+}
+
+/// SearchCodeSegmentDeclaration - Read tokens until we get to the specified code segment declaration.
+/// If we can't find it , return false;
+bool Parser::SearchCodeSegmentDeclaration(std::string Name){
+  while(SkipAnyUntil(tok::kw___code, StopBeforeMatch)){
+    if(NextToken().is(tok::identifier) && NextToken().getIdentifierInfo()->getName().str() == Name)
+      return true;
+    ConsumeToken();
+  }
+  return false;
+}
+
+bool Parser::NeedPrototypeDeclaration(Token IITok){
+  LookupResult LR(Actions, IITok.getIdentifierInfo(), IITok.getLocation(), Actions.LookupOrdinaryName);
+  CXXScopeSpec SS;
+  Actions.LookupParsedName(LR, getCurScope(), &SS, !(Actions.getCurMethodDecl()));
+
+  return (LR.getResultKind() == LookupResult::NotFound);
+}
+
+/// CreatePrototypeDeclaration - Create prototype declaration by it's definition.
+void Parser::CreatePrototypeDeclaration(){
+  // move to the top level scope
+  Scope *SavedScope = getCurScope();
+  DeclContext *SavedContext = Actions.CurContext;
+  sema::FunctionScopeInfo *SavedFSI = Actions.FunctionScopes.pop_back_val();
+  Actions.CurContext = static_cast<DeclContext *>(Actions.Context.getTranslationUnitDecl());
+  Scope *TopScope = getCurScope();
+  while(TopScope->getParent() != NULL)
+    TopScope = TopScope->getParent();
+  Actions.CurScope = TopScope;
+  
+  Token Next = NextToken();
+  Token CachedTokens[3] = {Next, PP.LookAhead(1)};
+  Token SavedToken = Tok;
+  Token IITok = Tok.is(tok::identifier) ? Tok : Next;
+  PP.ClearCache();
+  PP.ProtoParsing = true;
+  ProtoParsing = true;
+  
+  const DirectoryLookup *CurDir = nullptr;
+  FileID FID = PP.getSourceManager().createFileID(PP.getCurrentFileLexer()->getFileEntry(), IITok.getLocation(), SrcMgr::C_User);
+  PP.EnterSourceFile(FID,CurDir,IITok.getLocation());
+  ConsumeToken();
+
+  if(SearchCodeSegmentDeclaration(IITok.getIdentifierInfo()->getName().str())){
+    DeclGroupPtrTy ProtoDecl;
+    ParseTopLevelDecl(ProtoDecl);
+    // add declaration to AST.
+    if(ProtoDecl)
+      (&Actions.getASTConsumer())->HandleTopLevelDecl(ProtoDecl.get());
+    // File Closing
+    Token T;
+    PP.HandleEndOfFile(T, false);
+
+    // recover tokens.
+    Tok = SavedToken;
+    PP.RestoreTokens(CachedTokens, 2);
+    
+  }
+  else {
+    // recover tokens.
+    CachedTokens[2] = Tok;
+    Tok = SavedToken;
+    PP.RestoreTokens(CachedTokens, 3);
+  }
+
+  // move to the previous scope.
+  Actions.CurScope = SavedScope;
+  Actions.CurContext = SavedContext;
+  Actions.FunctionScopes.push_back(SavedFSI);
+  
+  ProtoParsing = false;
+  PP.ProtoParsing = false;
+}
+
+static bool HasFlagsSet(Parser::SkipUntilFlags L, Parser::SkipUntilFlags R) {
+  return (static_cast<unsigned>(L) & static_cast<unsigned>(R)) != 0;
+}
+
+bool Parser::SkipAnyUntil(tok::TokenKind T, SkipUntilFlags Flags){
+  const PreprocessorLexer *L = PP.getCurrentFileLexer();
+  while(1){
+    if(Tok.is(T)){
+      if (HasFlagsSet(Flags, StopBeforeMatch)) {
+        // Noop, don't consume the token.
+      } else {
+        ConsumeAnyToken();
+      }
+      return true;
+    }
+    else if(PP.getCurrentFileLexer() != L){
+      return false;
+    }
+
+    ConsumeAnyToken();
+  }
+}
+
+#endif