123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632(**************************************************************************)(* This file is part of BINSEC. *)(* *)(* Copyright (C) 2016-2025 *)(* CEA (Commissariat à l'énergie atomique et aux énergies *)(* alternatives) *)(* *)(* you can redistribute it and/or modify it under the terms of the GNU *)(* Lesser General Public License as published by the Free Software *)(* Foundation, version 2.1. *)(* *)(* It is distributed in the hope that it will be useful, *)(* but WITHOUT ANY WARRANTY; without even the implied warranty of *)(* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the *)(* GNU Lesser General Public License for more details. *)(* *)(* See the GNU Lesser General Public License version 2.1 *)(* for more details (enclosed in the file licenses/LGPLv2.1). *)(* *)(**************************************************************************)openLibparsermoduleS=Basic_types.Stringtypeenv={wordsize:int;endianness:Machine.endianness;define:Dba.Var.t->Lexing.position->unit;origin:string->Lexing.positionoption;lookup:string->Dba.LValue.t;lookup_symbol:string->Dba.Var.Tag.attribute->Dba.Expr.t;}type'aloc='aAst.locmoduleSymbol=Ast.SymbolmoduleLoc=Ast.LocmoduleExpr=Ast.ExprmoduleInstr=Ast.InstrexceptionInference_failureofExpr.tlocexceptionInvalid_sizeofExpr.tloc*int*intexceptionInvalid_operationofExpr.tlocexceptionInvalid_annotationof(Loc.tloc*int*Lexing.positionoption)let_=Printexc.register_printer(function|Inference_failure(e,pos)->Some(Format.asprintf"@[<v>Unable to infer the size of %a %a@]"Expr.ppeParse_utils.pp_pospos)|Invalid_size((e,pos),size,expect)->Some(Format.asprintf"@[<v>Invalid size for %a (expected %d, got %d) %a@]"Expr.ppeexpectsizeParse_utils.pp_pospos)|Invalid_operation(e,pos)->Some(Format.asprintf"@[<v>Invalid operation in %a %a@]"Expr.ppeParse_utils.pp_pospos)|Invalid_annotation((var,pos),_,Somepos')->Some(Format.asprintf"@[<v>Conflicting size annotation in %a %a@ Previous definition \
%a@]"Loc.ppvarParse_utils.pp_posposParse_utils.pp_pospos')|Invalid_annotation((var,pos),size,None)->Some(Format.asprintf"@[<v>Invalid size annotation in %a (expected <%d>) %a@]"Loc.ppvarsizeParse_utils.pp_pospos)|_->None)letreceval_expr?size((e,p)ast:Expr.tloc)env=lete=matchewith|Int(z,_)->(matchsizewith|None->raise(Inference_failuret)|Somesize->(ifZ.numbitsz>sizethenletline=p.pos_lnumandcolumn=p.pos_cnum-p.pos_bol-1inOptions.Logger.warning"integer %a (line %d, column %d) does not fit in a bitvector \
of %d bit%s"Expr.ppelinecolumnsize(ifsize>1then"s"else""));Dba.Expr.constant(Bitvector.createzsize))|Bvbv->Dba.Expr.constantbv|Symbol((name,attr),_)->env.lookup_symbolnameattr|Loc(Sub({hi;lo},loc),_)->Dba.Expr.restrictlohi(Dba.LValue.to_expr(eval_loc?size:Nonelocenv))|Locloc->Dba.LValue.to_expr(eval_loc?sizelocenv)|Unary(op,x)->letsize=matchopwithRestrict_|Uext_|Sext_->None|_->sizeinDba.Expr.unaryop(eval_expr?sizexenv)|Binary(op,x,y)->letx,y=eval_binary?size~opxyenvinDba.Expr.binaryopxy|Ite(q,x,y)->letq=eval_expr~size:1qenvinletx,y=eval_binary?sizexyenvinDba.Expr.iteqxyinOption.iter(funsize->letsize'=Dba.Expr.size_ofeinifsize'<>sizethenraise(Invalid_size(t,size',size)))size;eandeval_binary?(first=true)?size?opxyenv=matcheval_expr?size:(matchopwith|None->size|Some(Plus|Minus|Mult|DivU|DivS|ModU|ModS|Or|And|Xor|LShift|RShiftU|RShiftS|LeftRotate|RightRotate)->size|Some_->None)xenvwith|x->(x,eval_expr?size:(matchopwith|SomeConcat->(matchsizewith|None->None|Somesize->Some(size-Dba.Expr.size_ofx))|None|Some_->Some(Dba.Expr.size_ofx))yenv)|exceptionInference_failure_whenfirst->lety,x=eval_binary~first:false?size?opyxenvin(x,y)andeval_int((e,_)ast:Expr.tloc)env=matchewith|Int(z,_)->ifnot(Z.fits_intz)thenraise(Invalid_operationt);Z.to_intz|Bvbv->ifnot(Z.fits_int(Bitvector.signed_ofbv))thenraise(Invalid_operationt);Bitvector.to_intbv|Symbol((name,attr),_)->(matchenv.lookup_symbolnameattrwith|Var{info=Symbol(_,(lazybv));_}->ifnot(Z.fits_int(Bitvector.value_ofbv))thenraise(Invalid_operationt);Bitvector.to_uintbv|_->raise(Invalid_operationt))|Unary(UMinus,x)->-eval_intxenv|Binary(Plus,x,y)->eval_intxenv+eval_intyenv|Binary(Minus,x,y)->eval_intxenv-eval_intyenv|Binary(Mult,x,y)->eval_intxenv*eval_intyenv|Binary(DivS,x,y)->eval_intxenv/eval_intyenv|Loc_|Unary_|Binary_|Ite_->raise(Invalid_operationt)anddeclare_varnamesizeposenv=letvar=Dba.Var.createname~bitsize:(Size.Bit.createsize)~tag:Emptyinenv.definevarpos;Dba.LValue.vvarandeval_var?size((_,p)ast)name(annot:Ast.Size.t)env=letlval=matchenv.lookupnamewith|lval->letsize'=matchannotwith|Explicitsize->size|Sizeoflval->letlval=eval_loclvalenvinDba.LValue.size_oflval|Evalexpr->letsize=eval_intexprenvinifsize<0thenraise(Invalid_operationexpr);size|Implicit->Dba.LValue.size_oflvalandsize=Dba.LValue.size_oflvalinifsize<>size'thenraise(Invalid_annotation(t,size,env.originname));lval|exceptionNot_found->(matchannotwith|Explicitsize->declare_varnamesizepenv|Sizeoflval->letlval=eval_loclvalenvindeclare_varname(Dba.LValue.size_oflval)penv|Evalexpr->letsize=eval_intexprenvinifsize<0thenraise(Invalid_operationexpr);declare_varnamesizepenv|Implicit->(matchsizewith|None->raise(Inference_failure(Expr.loct,p))|Somesize->declare_varnamesizepenv))inOption.iter(funsize->letsize'=Dba.LValue.size_oflvalinifsize'<>sizethenraise(Invalid_size((Expr.loct,p),size',size)))size;lvalandeval_loc?size((l,p)ast:Loc.tloc)env=letlval=matchlwith|Var(name,annot)->eval_var?sizetnameannotenv|Load(len,endianness,addr,array)->letendianness=Option.fold~none:env.endianness~some:Fun.idendiannessinletaddr=eval_expr~size:env.wordsizeaddrenvinDba.LValue.store(Size.Byte.createlen)endiannessaddr?array|Sub({hi;lo},((Var(name,annot),_)ast'))->(matcheval_var?sizet'nameannotenvwith|Varvar->Dba.LValue.restrictvarlohi|Restrict(var,{hi=hi';lo=lo'})->ifhi'<hi+lo'thenraise(Invalid_operation(Expr.loct,p));Dba.LValue.restrictvar(lo+lo')(hi+lo')|_->raise(Invalid_operation(Expr.loct,p)))|Sub_->raise(Invalid_operation(Expr.loct,p))inOption.iter(funsize->letsize'=Dba.LValue.size_oflvalinifsize'<>sizethenraise(Invalid_size((Expr.loct,p),size',size)))size;lvalmoduleOutput=structtypeformat=Types.Output.format=Bin|Dec|Hex|Asciitypet=|Model|Formula|Sliceof(Expr.tloc*string)list|Valueofformat*Expr.tloc|Streamofstring|Stringofstringoption*Expr.tloc*Expr.tlocoptionletevalenv(t:t):Types.Output.t=matchtwith|Model->Model|Formula->Formula|Slicevalues->Slice(List.map(fun(e,name)->(eval_expreenv,name))values)|Value(fmt,e)->Value(fmt,eval_expreenv)|Streamname->Streamname|String(array,offset,size)->String{array;offset=eval_expr~size:env.wordsizeoffsetenv;size=Option.map(fune->eval_expr~size:env.wordsizeeenv)size;}letformat_str=function|Bin->"bin"|Dec->"dec"|Hex->"hexa"|Ascii->"ascii"letppppf=function|Model->Format.pp_print_stringppf"model"|Formula->Format.pp_print_stringppf"formula"|Slicedefs->Format.fprintfppf"formula for %a"(Format.pp_print_list~pp_sep:(funppf()->Format.pp_print_stringppf", ")(funppf((expr,_),name)->Format.fprintfppf"%a as %s"Expr.ppexprname))defs|Value(fmt,(e,_))->Format.fprintfppf"%s %a"(format_strfmt)Expr.ppe|Streamname->Format.fprintfppf"ascii stream %s"name|String(array,(offset,_),size)->Format.fprintfppf"c string %s[%a, %a]"(Option.value~default:"@"array)Expr.ppoffset(funppf->function|None->Format.pp_print_charppf'*'|Some(size,_)->Expr.ppppfsize)sizeendtypeAst.Obj.t+=|Intofint|Int_listofintlist|FormatofOutput.format|OutputofOutput.t|Output_listofOutput.tlist|String_listofstringlist|String_sliceofExpr.tloc*Expr.tlocoption|Key_valof(string*string)|Key_val_listof(string*string)list|Symbol_listofSymbol.tloclist|Loc_optofLoc.tlocoption|Loc_opt_listofLoc.tlocoptionlist|Expr_optofExpr.tlocoption|Expr_listofExpr.tloclist|Namedof(Expr.tloc*string)|Named_listof(Expr.tloc*string)listtypeAst.Instr.t+=|ArgumentofLoc.tloc*int(** [lval] := arg([i]) *)|ReturnofExpr.tlocoption(** return [rval] *)|CutofExpr.tlocoption|PrintofOutput.t|Reachofint*Expr.tlocoption*Output.tlist|Enumerateofint*Expr.tloc|ErrorofstringtypeAst.t+=|Starting_fromofExpr.tloc*Instr.tlist|Starting_from_coreofInstr.tlist|Load_sectionsofstringlist|Load_dataofLoc.tloc|Concretize_stack_pointer|Import_symbolsofSymbol.tloclist*string|HookofExpr.tloclist*Instr.tlist*bool|Return_hookofAst.Symbol.tloc*Instr.tlist|DecodeofBinstream.t*Instr.tlist|InitofInstr.tlist|Explore_allletpp_comma_listpp=Format.pp_print_list~pp_sep:(funppf()->Format.pp_print_stringppf", ")ppletpp_exprs=pp_comma_list(funppf(e,_)->Expr.ppppfe)letpp_outputs=Format.pp_print_list~pp_sep:(funppf()->Format.pp_print_stringppf" and ")(funppfoutput->Format.fprintfppf"print %a"Output.ppoutput)let()=Ast.Instr.register_pp(funppfinst->matchinstwith|Argument((lval,_),n)->Format.fprintfppf"%a := arg(%d)"Loc.pplvaln;true|ReturnNone->Format.pp_print_stringppf"return";true|Return(Some(rval,_))->Format.fprintfppf"return %a"Expr.pprval;true|Cutguard->Format.fprintfppf"cut %a"(funppfguard->Option.iter(fun(test,_)->Format.fprintfppf" if %a"Expr.pptest)guard)guard;true|Printoutput->Format.fprintfppf"print %a"Output.ppoutput;true|Enumerate(n,(rval,_))->Format.fprintfppf"enumerate%s %a%a"(ifn=max_intthen"*"else"")Expr.pprval(funppfn->ifn<>1&&n<>max_intthenFormat.fprintfppf" (%d)"n)n;true|Reach(n,guard,outputs)->Format.fprintfppf"reach%s%a%a%a"(ifn<0then"*"else"")(funppfn->if1<nthenFormat.fprintfppf" %d times"n)n(funppfguard->Option.iter(fun(test,_)->Format.fprintfppf" such that %a"Expr.pptest)guard)guard(funppfoutputs->ifoutputs<>[]thenFormat.fprintfppf" then %a"pp_outputsoutputs)outputs;true|Errormsg->Format.fprintfppf"error %S"msg;true|_->false)letpp_stmts=Format.pp_print_list~pp_sep:Format.pp_print_spaceInstr.ppletpp_with_stmtsppfstmts=matchstmtswith|[]->Format.pp_close_boxppf()|stmts->Format.fprintfppf" with@ %a@]@ end"pp_stmtsstmtsletdecl_printers=ref[]letregister_pppp=decl_printers:=pp::!decl_printersletrecresolve_ppppfdecl=function|[]->Format.pp_print_stringppf"unknown"|pp::printers->ifnot(ppppfdecl)thenresolve_ppppfdeclprintersletpp_options=Format.pp_print_list~pp_sep:(funppf()->Format.pp_print_charppf',')(funppf(k,v)->Format.fprintfppf"%S"k;ifv<>""thenFormat.fprintfppf"=%S"v)letppppfdecl=matchdeclwith|Starting_from((addr,_),stmts)->Format.fprintfppf"@[<v>@[<v 2>starting from %a%a@]"Expr.ppaddrpp_with_stmtsstmts|Starting_from_corestmts->Format.fprintfppf"@[<v>@[<v 2>starting from core%a@]"pp_with_stmtsstmts|Load_sections[name]->Format.fprintfppf"load section %s from file"name|Load_sectionsnames->Format.fprintfppf"load sections %a from file"(Format.pp_print_list~pp_sep:(funppf()->Format.pp_print_stringppf", ")Format.pp_print_string)names|Load_data(store,_)->Format.fprintfppf"%a from file"Loc.ppstore|Concretize_stack_pointer->Format.pp_print_stringppf"with concrete stack pointer"|Import_symbols(symbols,file)->Format.fprintfppf"import %a from %s"(pp_comma_list(funppf(sym,_)->Symbol.ppppfsym))symbolsfile|Hook(addr,stmts,_)->Format.fprintfppf"@[<v>@[<v 2>hook %a with@ %a@]@ end@]"pp_exprsaddrpp_stmtsstmts|Return_hook((symbol,_),stmts)->Format.fprintfppf"@[<v>@[<v 2>hook %a return with@ %a@]@ end@]"Ast.Symbol.ppsymbolpp_stmtsstmts|Decode(opcode,stmts)->Format.fprintfppf"@[<v>@[<v 2>hook opcode %a by@ %a@]@ end@]"Binstream.ppopcodepp_stmtsstmts|Initstmts->Format.fprintfppf"@[<v>%a@]"pp_stmtsstmts|Explore_all->Format.pp_print_stringppf"explore all"|_->resolve_ppppfdecl!decl_printerslet_pp_globalppfglobal_data=Format.fprintfppf"@[<v>%a@]"(funppfmap->S.Map.iter(funnamevalues->Format.fprintfppf"@[<h>%s: %a@]@ "name(funppfset->S.Set.iter(funvalue->Format.fprintfppf"%s@ "value)set)values)map)global_dataletgrammar:(unit,Libparser.obj,unit,unit,Libparser.objDyp.dyplexbuf)Dyp.dyp_actionlist=[Dyp.Bind_to_cons[("byte","Obj");("byte_rev_list","Obj");("key_value","Obj");("comma_separated_key_value_rev_list","Obj");("options","Obj");("format","Obj");("named","Obj");("comma_separated_named_rev_list","Obj");("output","Obj");("and_separated_output_rev_list","Obj");("outputs","Obj");("string_slice","Obj");("times","Obj");("such_that","Obj");("guard","Obj");("num","Obj");("qident","String");("section","String");("comma_separated_section_rev_list","Obj");("comma_separated_symbol_rev_list","Obj");("arg","Obj");("comma_separated_arg_rev_list","Obj");("arguments","Stmt");("expr_opt","Obj");("comma_separated_expr_rev_list","Obj");("with_stmts_end","Stmt");("directive","Stmt");("decl","Decl");("rev_program","Program");("program","Program");];Dyp.Add_rules[(("byte",[Dyp.Regexp(Dyp.RE_Seq[Dyp.RE_Name"hexdigit";Dyp.RE_Name"hexdigit"]);],"default_priority",[]),fun_->function|[Syntax.Lexeme_matchedbyte]->(Syntax.Obj(Int(Z.to_int(Z.of_string_base16byte))),[])|_->assertfalse);(("byte_rev_list",[],"default_priority",[]),fun__->(Syntax.Obj(Int_list[]),[]));(("byte_rev_list",[Dyp.Non_ter("byte_rev_list",No_priority);Dyp.Non_ter("byte",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(Int_listbytes);Syntax.Obj(Intbyte)]->(Syntax.Obj(Int_list(byte::bytes)),[])|_->assertfalse);(("key_value",[Dyp.Non_ter("qident",No_priority)],"default_priority",[]),fun_->function|[Syntax.Stringkey]->(Syntax.Obj(Key_val(key,"")),[])|_->assertfalse);(("key_value",[Dyp.Non_ter("qident",No_priority);Dyp.Regexp(RE_Char'=');Dyp.Non_ter("qident",No_priority);],"default_priority",[]),fun_->function|[Syntax.Stringkey;_;Syntax.Stringvalue]->(Syntax.Obj(Key_val(key,value)),[])|_->assertfalse);(("comma_separated_key_value_rev_list",[Dyp.Non_ter("key_value",No_priority)],"default_priority",[]),fun_->function|[Syntax.Obj(Key_valpair)]->(Syntax.Obj(Key_val_list[pair]),[])|_->assertfalse);(("comma_separated_key_value_rev_list",[Dyp.Non_ter("comma_separated_key_value_rev_list",No_priority);Dyp.Regexp(RE_Char',');Dyp.Non_ter("key_value",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(Key_val_listl);_;Syntax.Obj(Key_valpair)]->(Syntax.Obj(Key_val_list(pair::l)),[])|_->assertfalse);(("options",[],"default_priority",[]),fun__->(Syntax.Obj(Key_val_list[]),[]));(("options",[Dyp.Regexp(RE_Char'[');Dyp.Non_ter("comma_separated_key_value_rev_list",No_priority);Dyp.Regexp(RE_Char']');],"default_priority",[]),fun_->function|[_;Syntax.Obj(Key_val_listl);_]->(Syntax.Obj(Key_val_list(List.revl)),[])|_->assertfalse);(("num",[],"default_priority",[]),fun__->(Syntax.Obj(Int1),[]));(("num",[Dyp.Regexp(RE_Char'(');Dyp.Non_ter("int",No_priority);Dyp.Regexp(RE_Char')');],"default_priority",[]),fun_->function|[_;Syntax.Obj_intn;_]->(Syntax.Obj(Int(Z.to_intn)),[])|_->assertfalse);(("times",[],"default_priority",[]),fun__->(Syntax.Obj(Int1),[]));(("times",[Dyp.Non_ter("int",No_priority);Dyp.Regexp(RE_String"times")],"default_priority",[]),fun_->function|[Syntax.Obj_intn;_]->(Syntax.Obj(Int(Z.to_intn)),[])|_->assertfalse);(("format",[],"default_priority",[]),fun__->(Syntax.Obj(FormatOutput.Hex),[]));(("format",[Dyp.Regexp(RE_String"ascii")],"default_priority",[]),fun_->function_->(Syntax.Obj(FormatOutput.Ascii),[]));(("format",[Dyp.Regexp(RE_String"hexa")],"default_priority",[]),fun_->function_->(Syntax.Obj(FormatOutput.Hex),[]));(("format",[Dyp.Regexp(RE_String"bin")],"default_priority",[]),fun_->function_->(Syntax.Obj(FormatOutput.Bin),[]));(("format",[Dyp.Regexp(RE_String"dec")],"default_priority",[]),fun_->function_->(Syntax.Obj(FormatOutput.Dec),[]));(("named",[Dyp.Non_ter("var",No_priority)],"default_priority",[]),fun_->function|[Syntax.Loc((Loc.Var(name,_),pos)asvar)]->(Syntax.Obj(Named((Expr.locvar,pos),name)),[])|_->assertfalse);(("named",[Dyp.Non_ter("expr",No_priority);Dyp.Regexp(RE_String"as");Dyp.Non_ter("ident",No_priority);],"default_priority",[]),fun_->function|[Syntax.Exprexpr;_;Syntax.Stringalias]->(Syntax.Obj(Named(expr,alias)),[])|_->assertfalse);(("comma_separated_named_rev_list",[Dyp.Non_ter("named",No_priority)],"default_priority",[]),fun_->function|[Syntax.Obj(Namedterm)]->(Syntax.Obj(Named_list[term]),[])|_->assertfalse);(("comma_separated_named_rev_list",[Dyp.Non_ter("comma_separated_named_rev_list",No_priority);Dyp.Regexp(RE_Char',');Dyp.Non_ter("named",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(Named_listl);_;Syntax.Obj(Namedterm)]->(Syntax.Obj(Named_list(term::l)),[])|_->assertfalse);(("output",[Dyp.Regexp(RE_String"print");Dyp.Regexp(RE_String"formula")],"default_priority",[]),fun_->function_->(Syntax.Obj(OutputOutput.Formula),[]));(("output",[Dyp.Regexp(RE_String"print");Dyp.Regexp(RE_String"formula");Dyp.Regexp(RE_String"for");Dyp.Non_ter("comma_separated_named_rev_list",No_priority);],"default_priority",[]),fun_->function|[_;_;_;Syntax.Obj(Named_listterms)]->(Syntax.Obj(Output(Output.Slice(List.revterms))),[])|_->assertfalse);(("output",[Dyp.Regexp(RE_String"print");Dyp.Regexp(RE_String"model")],"default_priority",[]),fun__->(Syntax.Obj(OutputOutput.Model),[]));(("output",[Dyp.Regexp(RE_String"print");Dyp.Non_ter("format",No_priority);Dyp.Non_ter("expr",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Obj(Formatformat);Syntax.Exprterm]->(Syntax.Obj(Output(Output.Value(format,term))),[])|_->assertfalse);(("output",[Dyp.Regexp(RE_String"print");Dyp.Regexp(RE_String"ascii");Dyp.Regexp(RE_String"stream");Dyp.Non_ter("ident",No_priority);],"default_priority",[]),fun_->function|[_;_;_;Syntax.Stringname]->(Syntax.Obj(Output(Output.Streamname)),[])|_->assertfalse);(("string_slice",[],"default_priority",[]),fun_->function|_->(Syntax.Obj(String_slice((Expr.integerZ.zero,Lexing.dummy_pos),None)),[]));(("string_slice",[Dyp.Regexp(RE_Char'[');Dyp.Non_ter("expr",No_priority);Dyp.Regexp(RE_Char']');],"default_priority",[]),fun_->function|[_;Syntax.Exprexpr;_]->(Syntax.Obj(String_slice(expr,None)),[])|_->assertfalse);(("string_slice",[Dyp.Regexp(RE_Char'[');Dyp.Non_ter("expr",No_priority);Dyp.Regexp(RE_Char',');Dyp.Regexp(RE_Char'*');Dyp.Regexp(RE_Char']');],"default_priority",[]),fun_->function|[_;Syntax.Exprexpr;_;_;_]->(Syntax.Obj(String_slice(expr,None)),[])|_->assertfalse);(("string_slice",[Dyp.Regexp(RE_Char'[');Dyp.Non_ter("expr",No_priority);Dyp.Regexp(RE_Char',');Dyp.Non_ter("expr",No_priority);Dyp.Regexp(RE_Char']');],"default_priority",[]),fun_->function|[_;Syntax.Exproffset;_;Syntax.Exprsize;_]->(Syntax.Obj(String_slice(offset,Somesize)),[])|_->assertfalse);(("output",[Dyp.Regexp(RE_String"print");Dyp.Regexp(RE_String"c");Dyp.Regexp(RE_String"string");Dyp.Non_ter("array",No_priority);Dyp.Non_ter("string_slice",No_priority);],"default_priority",[]),fun_->function|[_;_;_;Syntax.Obj_arrayarray;Syntax.Obj(String_slice(offset,size));]->(Syntax.Obj(Output(Output.String(array,offset,size))),[])|_->assertfalse);(("and_separated_output_rev_list",[Dyp.Non_ter("output",No_priority)],"default_priority",[]),fun_->function|[Syntax.Obj(Outputoutput)]->(Syntax.Obj(Output_list[output]),[])|_->assertfalse);(("and_separated_output_rev_list",[Dyp.Non_ter("and_separated_output_rev_list",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Regexp(RE_String"and");Dyp.Non_ter("output",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(Output_listl);_;_;Syntax.Obj(Outputoutput)]->(Syntax.Obj(Output_list(output::l)),[])|_->assertfalse);(("outputs",[],"default_priority",[]),fun_->function_->(Syntax.Obj(Output_list[]),[]));(("outputs",[Dyp.Regexp(RE_String"then");Dyp.Non_ter("and_separated_output_rev_list",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Obj(Output_listl)]->(Syntax.Obj(Output_list(List.revl)),[])|_->assertfalse);(("qident",[Dyp.Non_ter("ident",No_priority)],"default_priority",[]),fun_->function|[Syntax.Stringid]->(Syntax.Stringid,[])|_->assertfalse);(("qident",[Dyp.Ter"CONST"],"default_priority",[]),fun_->function|[Syntax.Obj_CONSTbv]->(Syntax.String(Bitvector.to_asciistringbv),[])|_->assertfalse);(("section",[Dyp.Non_ter("qident",No_priority)],"default_priority",[]),fun_->function|[Syntax.Stringid]->(Syntax.Stringid,[])|_->assertfalse);(("section",[Dyp.Non_ter("label",No_priority)],"default_priority",[]),fun_->function|[Syntax.Stringid]->(Syntax.String("."^id),[])|_->assertfalse);(("comma_separated_section_rev_list",[Dyp.Non_ter("section",No_priority)],"default_priority",[]),fun_->function|[Syntax.Stringsection]->(Syntax.Obj(String_list[section]),[])|_->assertfalse);(("comma_separated_section_rev_list",[Dyp.Non_ter("comma_separated_section_rev_list",No_priority);Dyp.Regexp(RE_Char',');Dyp.Non_ter("section",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(String_listl);_;Syntax.Stringsection]->(Syntax.Obj(String_list(section::l)),[])|_->assertfalse);(("comma_separated_symbol_rev_list",[Dyp.Non_ter("symbol",No_priority)],"default_priority",[]),fun_->function|[Syntax.Symbolsym]->(Syntax.Obj(Symbol_list[sym]),[])|_->assertfalse);(("comma_separated_symbol_rev_list",[Dyp.Non_ter("comma_separated_symbol_rev_list",No_priority);Dyp.Regexp(RE_Char',');Dyp.Non_ter("symbol",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(Symbol_listl);_;Syntax.Symbolsym]->(Syntax.Obj(Symbol_list(sym::l)),[])|_->assertfalse);(("arg",[Dyp.Non_ter("var",No_priority)],"default_priority",[]),fun_->function|[Syntax.Locvar]->(Syntax.Obj(Loc_opt(Somevar)),[])|_->assertfalse);(("arg",[Dyp.Regexp(RE_Char'_')],"default_priority",[]),fun__->(Syntax.Obj(Loc_optNone),[]));(("comma_separated_arg_rev_list",[Dyp.Non_ter("arg",No_priority)],"default_priority",[]),fun_->function|[Syntax.Obj(Loc_optarg)]->(Syntax.Obj(Loc_opt_list[arg]),[])|_->assertfalse);(("comma_separated_arg_rev_list",[Dyp.Non_ter("comma_separated_arg_rev_list",No_priority);Dyp.Regexp(RE_Char',');Dyp.Non_ter("arg",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(Loc_opt_listl);_;Syntax.Obj(Loc_optarg)]->(Syntax.Obj(Loc_opt_list(arg::l)),[])|_->assertfalse);(("arguments",[],"default_priority",[]),fun__->(Syntax.Stmt[],[]));(("arguments",[Dyp.Regexp(RE_Char'(');Dyp.Regexp(RE_Char')')],"default_priority",[]),fun__->(Syntax.Stmt[],[]));(("arguments",[Dyp.Regexp(RE_Char'(');Dyp.Non_ter("comma_separated_arg_rev_list",No_priority);Dyp.Regexp(RE_Char')');],"default_priority",[]),fun_->function|[_;Syntax.Obj(Loc_opt_listargs);_]->(Syntax.Stmt(List.mapi(funiarg->Option.fold~none:Instr.Nop~some:(funname->Argument(name,i))arg)(List.revargs)),[])|_->assertfalse);(("expr_opt",[],"default_priority",[]),fun__->(Syntax.Obj(Expr_optNone),[]));(("expr_opt",[Dyp.Non_ter("expr",No_priority)],"default_priority",[]),fun_->function|[Syntax.Exprexpr]->(Syntax.Obj(Expr_opt(Someexpr)),[])|_->assertfalse);(("control",[Dyp.Regexp(RE_String"return");Dyp.Non_ter("expr_opt",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Obj(Expr_optexpr)]->(Syntax.Stmt[Returnexpr],[])|_->assertfalse);(("comma_separated_expr_rev_list",[Dyp.Non_ter("expr",No_priority)],"default_priority",[]),fun_->function|[Syntax.Exprexpr]->(Syntax.Obj(Expr_list[expr]),[])|_->assertfalse);(("comma_separated_expr_rev_list",[Dyp.Non_ter("comma_separated_expr_rev_list",No_priority);Dyp.Regexp(RE_Char',');Dyp.Non_ter("expr",No_priority);],"default_priority",[]),fun_->function|[Syntax.Obj(Expr_listl);_;Syntax.Exprexpr]->(Syntax.Obj(Expr_list(expr::l)),[])|_->assertfalse);(("with_stmts_end",[],"default_priority",[]),fun__->(Syntax.Stmt[],[]));(("with_stmts_end",[Dyp.Regexp(RE_String"with");Dyp.Non_ter("stmts",No_priority);Dyp.Regexp(RE_String"end");],"default_priority",[]),fun_->function|[_;Syntax.Stmtstmts;_]->(Syntax.Stmtstmts,[])|_->assertfalse);(("such_that",[],"default_priority",[]),fun__->(Syntax.Obj(Expr_optNone),[]));(("such_that",[Dyp.Regexp(RE_String"such");Dyp.Regexp(RE_String"that");Dyp.Non_ter("expr",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Exprguard]->(Syntax.Obj(Expr_opt(Someguard)),[])|_->assertfalse);(("guard",[],"default_priority",[]),fun__->(Syntax.Obj(Expr_optNone),[]));(("guard",[Dyp.Regexp(RE_String"if");Dyp.Non_ter("expr",No_priority)],"default_priority",[]),fun_->function|[_;Syntax.Exprguard]->(Syntax.Obj(Expr_opt(Someguard)),[])|_->assertfalse);(("directive",[Dyp.Regexp(RE_String"enumerate");Dyp.Non_ter("expr",No_priority);Dyp.Non_ter("num",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Exprexpr;Syntax.Obj(Intn)]->(Syntax.Stmt[Enumerate(n,expr)],[])|_->assertfalse);(("directive",[Dyp.Regexp(RE_String"enumerate");Dyp.Regexp(RE_Char'*');Dyp.Non_ter("expr",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Exprexpr]->(Syntax.Stmt[Enumerate(max_int,expr)],[])|_->assertfalse);(("directive",[Dyp.Regexp(RE_String"assume");Dyp.Non_ter("expr",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Exprexpr]->(Syntax.Stmt[Instr.Assumeexpr],[])|_->assertfalse);(("directive",[Dyp.Regexp(RE_String"assert");Dyp.Non_ter("expr",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Exprexpr]->(Syntax.Stmt[Instr.Assertexpr],[])|_->assertfalse);(("fallthrough",[Dyp.Non_ter("output",No_priority)],"default_priority",[]),fun_->function|[Syntax.Obj(Outputoutput)]->(Syntax.Instr(Printoutput),[])|_->assertfalse);(("fallthrough",[Dyp.Regexp(RE_String"enumerate");Dyp.Non_ter("expr",No_priority);Dyp.Non_ter("num",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Exprexpr;Syntax.Obj(Intn)]->(Syntax.Instr(Enumerate(n,expr)),[])|_->assertfalse);(("fallthrough",[Dyp.Regexp(RE_String"reach");Dyp.Non_ter("times",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("such_that",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("outputs",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Obj(Intn);_;Syntax.Obj(Expr_optguard);_;Syntax.Obj(Output_listoutputs);]->(Syntax.Instr(Reach(n,guard,outputs)),[])|_->assertfalse);(("fallthrough",[Dyp.Regexp(RE_String"cut");Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("guard",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Obj(Expr_optguard)]->(Syntax.Instr(Cutguard),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"starting");Dyp.Regexp(RE_String"from");Dyp.Non_ter("expr",No_priority);Dyp.Non_ter("with_stmts_end",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Expraddr;Syntax.Stmtstmts]->(Syntax.Decl(Starting_from(addr,stmts)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"starting");Dyp.Regexp(RE_String"from");Dyp.Regexp(RE_String"core");Dyp.Non_ter("with_stmts_end",No_priority);],"default_priority",[]),fun_->function|[_;_;_;Syntax.Stmtstmts]->(Syntax.Decl(Starting_from_corestmts),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"load");Dyp.Regexp(RE_String"section");Dyp.Non_ter("section",No_priority);Dyp.Regexp(RE_String"from");Dyp.Regexp(RE_String"file");],"default_priority",[]),fun_->function|[_;_;Syntax.Stringsection;_;_]->(Syntax.Decl(Load_sections[section]),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"load");Dyp.Regexp(RE_String"sections");Dyp.Non_ter("comma_separated_section_rev_list",No_priority);Dyp.Regexp(RE_String"from");Dyp.Regexp(RE_String"file");],"default_priority",[]),fun_->function|[_;_;Syntax.Obj(String_listsections);_;_]->(Syntax.Decl(Load_sectionssections),[])|_->assertfalse);(("decl",[Dyp.Non_ter("load",No_priority);Dyp.Regexp(RE_String"from");Dyp.Regexp(RE_String"file");],"default_priority",[]),fun_->function|[Syntax.Locload;_;_]->(Syntax.Decl(Load_dataload),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"import");Dyp.Non_ter("comma_separated_symbol_rev_list",No_priority);Dyp.Regexp(RE_String"from");Dyp.Non_ter("qident",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Obj(Symbol_listsyms);_;Syntax.Stringfile]->(Syntax.Decl(Import_symbols(syms,file)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"concretize");Dyp.Regexp(RE_String"stack");],"default_priority",[]),fun__->Options.Logger.warning"\"concretize stack\" is deprecated, use \"with concrete stack \
pointer\" instead";(Syntax.DeclConcretize_stack_pointer,[]));(("decl",[Dyp.Regexp(RE_String"with");Dyp.Regexp(RE_String"concrete");Dyp.Regexp(RE_String"stack");Dyp.Regexp(RE_String"pointer");],"default_priority",[]),fun__->(Syntax.DeclConcretize_stack_pointer,[]));(("decl",[Dyp.Regexp(RE_String"replace");Dyp.Regexp(RE_String"opcode");Dyp.Non_ter("byte_rev_list",No_priority);Dyp.Regexp(RE_String"by");Dyp.Non_ter("stmts",No_priority);Dyp.Regexp(RE_String"end");],"default_priority",[]),fun_->function|[_;_;Syntax.Obj(Int_listbytes);_;Syntax.Stmtstmts;_]->(Syntax.Decl(Decode(Binstream.of_list(List.revbytes),stmts)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"hook");Dyp.Non_ter("comma_separated_expr_rev_list",No_priority);Dyp.Non_ter("arguments",No_priority);Dyp.Regexp(RE_String"with");Dyp.Non_ter("stmts",No_priority);Dyp.Regexp(RE_String"end");],"default_priority",[]),fun_->function|[_;Syntax.Obj(Expr_listaddr);Syntax.Stmtargs;_;Syntax.Stmtstmts;_;]->(Syntax.Decl(Hook(addr,List.rev_appendargsstmts,true)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"replace");Dyp.Non_ter("comma_separated_expr_rev_list",No_priority);Dyp.Non_ter("arguments",No_priority);Dyp.Regexp(RE_String"by");Dyp.Non_ter("stmts",No_priority);Dyp.Regexp(RE_String"end");],"default_priority",[]),fun_->function|[_;Syntax.Obj(Expr_listaddr);Syntax.Stmtargs;_;Syntax.Stmtstmts;_;]->(Syntax.Decl(Hook(addr,List.rev_appendargsstmts,false)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"abort");Dyp.Regexp(RE_String"at");Dyp.Non_ter("comma_separated_expr_rev_list",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Obj(Expr_listaddr)]->(Syntax.Decl(Hook(addr,[Instr.dynamic_assert(Expr.zero,Lexing.dummy_pos);Instr.halt;],false)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"halt");Dyp.Regexp(RE_String"at");Dyp.Non_ter("comma_separated_expr_rev_list",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Obj(Expr_listaddr)]->(Syntax.Decl(Hook(addr,[Instr.halt],false)),[])|_->assertfalse);(("decl",[Dyp.Non_ter("instr",No_priority)],"default_priority",[]),fun_->function|[Syntax.Stmtinstr]->(Syntax.Decl(Initinstr),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"reach");Dyp.Regexp(RE_String"all")],"default_priority",[]),fun__->Options.Logger.warning"\"reach all\" is deprecated, use \"explore all\" instead";(Syntax.DeclExplore_all,[]));(("decl",[Dyp.Regexp(RE_String"explore");Dyp.Regexp(RE_String"all")],"default_priority",[]),fun__->(Syntax.DeclExplore_all,[]));(("decl",[Dyp.Regexp(RE_String"reach");Dyp.Non_ter("expr",No_priority);Dyp.Non_ter("arguments",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("times",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("such_that",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("outputs",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Expraddr;Syntax.Stmtargs;_;Syntax.Obj(Intn);_;Syntax.Obj(Expr_optguard);_;Syntax.Obj(Output_listoutputs);]->(Syntax.Decl(Hook([addr],List.rev_appendargs[Reach(n,guard,outputs)],true)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"reach");Dyp.Regexp(RE_Char'*');Dyp.Non_ter("expr",No_priority);Dyp.Non_ter("arguments",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("such_that",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("outputs",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Expraddr;Syntax.Stmtargs;_;Syntax.Obj(Expr_optguard);_;Syntax.Obj(Output_listoutputs);]->(Syntax.Decl(Hook([addr],List.rev_appendargs[Reach(-1,guard,outputs)],true)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"cut");Dyp.Regexp(RE_String"at");Dyp.Non_ter("expr",No_priority);Dyp.Non_ter("arguments",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("guard",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Expraddr;Syntax.Stmtargs;_;Syntax.Obj(Expr_optguard);]->(Syntax.Decl(Hook([addr],List.rev_appendargs[Cutguard],true)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"at");Dyp.Non_ter("expr",No_priority);Dyp.Non_ter("arguments",No_priority);Dyp.Non_ter("directive",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Expraddr;Syntax.Stmtargs;Syntax.Stmtstmts]->(Syntax.Decl(Hook([addr],List.rev_appendargsstmts,true)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"hook");Dyp.Non_ter("symbol",No_priority);Dyp.Regexp(RE_String"return");Dyp.Regexp(RE_String"with");Dyp.Non_ter("stmts",No_priority);Dyp.Regexp(RE_String"end");],"default_priority",[]),fun_->function|[_;Syntax.Symbolsym;_;_;Syntax.Stmtstmts;_]->(Syntax.Decl(Return_hook(sym,stmts)),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"abort");Dyp.Regexp(RE_String"at");Dyp.Non_ter("symbol",No_priority);Dyp.Regexp(RE_String"return");],"default_priority",[]),fun_->function|[_;_;Syntax.Symbolsymbol;_]->(Syntax.Decl(Return_hook(symbol,[Instr.dynamic_assert(Expr.zero,Lexing.dummy_pos);Instr.halt;])),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"halt");Dyp.Regexp(RE_String"at");Dyp.Non_ter("symbol",No_priority);Dyp.Regexp(RE_String"return");],"default_priority",[]),fun_->function|[_;_;Syntax.Symbolsymbol;_]->(Syntax.Decl(Return_hook(symbol,[Instr.halt])),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"reach");Dyp.Non_ter("symbol",No_priority);Dyp.Regexp(RE_String"return");Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("times",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("such_that",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("outputs",No_priority);],"default_priority",[]),fun_->function|[_;Syntax.Symbolsymbol;_;_;Syntax.Obj(Intn);_;Syntax.Obj(Expr_optguard);_;Syntax.Obj(Output_listoutputs);]->(Syntax.Decl(Return_hook(symbol,[Reach(n,guard,outputs)])),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"reach");Dyp.Regexp(RE_Char'*');Dyp.Non_ter("symbol",No_priority);Dyp.Regexp(RE_String"return");Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("such_that",No_priority);Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("outputs",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Symbolsymbol;_;_;Syntax.Obj(Expr_optguard);_;Syntax.Obj(Output_listoutputs);]->(Syntax.Decl(Return_hook(symbol,[Reach(-1,guard,outputs)])),[])|_->assertfalse);(("decl",[Dyp.Regexp(RE_String"cut");Dyp.Regexp(RE_String"at");Dyp.Non_ter("symbol",No_priority);Dyp.Regexp(RE_String"return");Dyp.Non_ter("accept_newline",No_priority);Dyp.Non_ter("guard",No_priority);],"default_priority",[]),fun_->function|[_;_;Syntax.Symbolsymbol;_;_;Syntax.Obj(Expr_optguard)]->(Syntax.Decl(Return_hook(symbol,[Cutguard])),[])|_->assertfalse);(("rev_program",[],"default_priority",[]),fun__->(Syntax.Program[],[]));(("rev_program",[Dyp.Non_ter("rev_program",No_priority);Dyp.Non_ter("decl",No_priority);Dyp.Non_ter("separator",No_priority);],"default_priority",[]),fun_->function|[Syntax.Programrev_program;Syntax.Decldecl;_]->(Syntax.Program(decl::rev_program),[Dyp.Keep_grammar])|_->assertfalse);(("program",[Dyp.Non_ter("rev_program",No_priority);Dyp.RegexpRE_Eof_char],"default_priority",[]),fun_->function|[Syntax.Programrev_program;_]->(Syntax.Program(List.revrev_program),[])|_->assertfalse);];]lettry_and_parsegrammar_extensionslexbuf=letpilot=Dyp.update_pp(Syntax.pp())(List.concat(grammar::grammar_extensions))inmatchDyp.lexparsepilot"program"lexbufwith|[(Syntax.Programast,_)]->ast|exceptionFailure_->lets=Format.asprintf"@[<v>Probable lexing error %a@]"Parse_utils.pp_pos(Dyp.lexeme_end_plexbuf)inraise(Parse_utils.UserFriendlyParseErrors)|_|(exceptionDyp.Syntax_error)->lets=Format.asprintf"@[<v>Parse error at word `%s' %a@]"(Dyp.lexemelexbuf)Parse_utils.pp_pos(Dyp.lexeme_end_plexbuf)inraise(Parse_utils.UserFriendlyParseErrors)typefile_stream=Openedofin_channel*stringlist|Pendingofstringlistletrecrefill_buflexbuffile_streambuflen=match!file_streamwith|Pending[]->0|Pending(filename::files)->(matchopen_infilenamewith|exceptionSys_error_->Options.Logger.fatal"Cannot open file %s"filename|ic->file_stream:=Opened(ic,files);Dyp.set_fname(Option.get!lexbuf)filename;letstd_lexbuf=Dyp.std_lexbuf(Option.get!lexbuf)inLexing.set_positionstd_lexbuf{pos_fname=filename;pos_lnum=0;pos_bol=0;pos_cnum=0};refill_buflexbuffile_streambuflen)|Opened(ic,files)->(matchinputicbuf0lenwith|0->close_inic;file_stream:=Pendingfiles;Bytes.setbuf0'\n';1|n->n)letread_filesgramma_extensionsfiles=letfile_stream=ref(Pendingfiles)andlexbuf=refNoneinlexbuf:=Some(Dyp.from_function(Libparser.Syntax.pp())(refill_buflexbuffile_stream));Fun.protect~finally:(fun()->match!file_streamwithOpened(ic,_)->close_inic|_->())(fun()->try_and_parsegramma_extensions(Option.get!lexbuf))(* include Cli.Make (struct *)(* let shortname = "ast" *)(* let name = "AST" *)(* end) *)(* module Parse = Builder.String_option (struct *)(* let name = "parse" *)(* let doc = "Parse AST node" *)(* end) *)(* let run () = *)(* Option.iter *)(* (fun node -> *)(* let lexbuf = Dyp.from_string (Syntax.pp ()) node in *)(* Logger.result "@[<v>%a@]" *)(* (Format.pp_print_list ~pp_sep:Format.pp_print_space pp) *)(* (try_and_parse lexbuf)) *)(* (Parse.get_opt ()) *)(* let _ = Cli.Boot.enlist ~name:"AST" ~f:run *)