1not_defined_for(Data,Function) :-
    2        Data = [Lang,Is_input|_],
    3        (Is_input ->
    4            true;
    5        writeln(Function),writeln('not defined for'),writeln(Lang)).
    6
    7optional_the(A) -->
    8	A;("the";"The"),ws_,A.
    9
   10langs_to_output(Data,Name,[]) -->
   11	{not_defined_for(Data,Name),true}.
   12
   13langs_to_output(Data,Name,[Langs:Output|Rest]) -->
   14	{
   15		Data = [Lang|_]
   16	},
   17	({memberchk(Lang,Langs)}->
   18		Output;
   19	langs_to_output(Data,Name,Rest)).
   20
   21return_(Data,[A]) -->
   22	{grammars(Grammars)},
   23    langs_to_output(Data,return,[
   24	['pseudocode','systemverilog','vhdl','lua','ruby','java','seed7','xl','e','livecode','englishscript','gap','kal','engscript','pawn','ada','powershell','rust','d','ceylon','typescript','hack','autohotkey','gosu','swift','pike','objective-c','c','groovy','scala','julia','dart','c#','javascript','go','haxe','php','c++','perl','vala','rebol','tcl','awk','bc','chapel','perl 6']:
   25			("return",ws_,A),
   26	['coffeescript','python','cython','cosmos']:
   27			("return",python_ws_,A),
   28	['english']:
   29			("return",python_ws_,A),
   30	Grammars:
   31			A,
   32	['minizinc','sympy','logtalk','pydatalog','polish notation','reverse polish notation','mathematical notation','emacs lisp','z3','erlang','maxima','standard ml','icon','oz','clips','newlisp','hy','sibilant','lispyscript','algol 68','clojure','common lisp','f#','ocaml','ml','racket','nemerle']:
   33			A,
   34	['pseudocode','visual basic','visual basic .net','autoit','monkey x']:
   35			("Return",ws_,A),
   36	['octave','fortran','picat']:
   37			("retval",ws,"=",ws,A),
   38	['cosmos','prolog','constraint handling rules']:
   39			("Return",python_ws,"=",python_ws,A),
   40	['haskell']:
   41			("return",python_ws,"=",python_ws,A),
   42	['pascal']:
   43			("Exit",ws,"(",ws,A,ws,")"),
   44	['pseudocode','r']:
   45			("return",ws,"(",ws,A,ws,")"),
   46	['wolfram']:
   47			("Return",ws,"[",ws,A,ws,"]"),
   48	['pop-11']:
   49			(A,ws,"->",ws,"Result"),
   50	['delphi','pascal']:
   51			("Result",ws,"=",ws,A),
   52	['pseudocode','sql']:
   53			("RETURN",ws_,A)
   54	]).
   55
   56initialize_constant_(Data,[Name,Type,Value]) -->
   57        langs_to_output(Data,initialize_constant,[
   58        ['seed7']:
   59                ("const",ws_,Type,ws,":",ws,Name,ws_,"is",ws_,Value),
   60        ['polish notation']:
   61                ("=",ws_,Name,ws_,Value),
   62        ['reverse polish notation']:
   63                (Name,ws_,Value,ws_,"="),
   64        ['fortran']:
   65                (Type,ws,",",ws,"PARAMETER",ws,"::",ws,Name,ws,"=",ws,"expression"),
   66        ['go']:
   67                ("const",ws_,Type,ws_,Name,ws,"=",ws,Value),
   68        ['perl 6']:
   69                ("constant",ws_,Type,ws_,Name,ws,"=",ws,Value),
   70        ['php','javascript','dart']:
   71                ("const",ws_,Name,ws,"=",ws,Value),
   72        ['z3']:
   73                ("(",ws,"declare-const",ws_,Name,ws_,Type,ws,")",ws,"(",ws,"assert",ws_,"(",ws,"=",ws_,Name,ws_,Value,ws,")",ws,")"),
   74        ['rust','swift']:
   75                ("let",ws_,Name,ws,"=",ws,Value),
   76        ['c++','c','d','c#']:
   77                ("const",ws_,Type,ws_,Name,ws,"=",ws,Value),
   78        ['common lisp']:
   79                ("(",ws,"setf",ws_,Name,ws_,Value,ws,")"),
   80        ['minizinc']:
   81                (Type,ws,":",ws,Name,ws,"=",ws,Value),
   82        ['scala']:
   83                ("val",ws_,Name,ws,":",ws,Type,ws,"=",ws,Value),
   84        ['erlang','julia','picat','prolog']:
   85                (Name,python_ws,"=",python_ws,Value),
   86        ['haskell']:
   87                (Name,python_ws,"<-",python_ws,Value),
   88        ['perl']:
   89                ("my",ws_,Name,ws,"=",ws,Value),
   90        ['rebol']:
   91                (Name,ws,":",ws,Value),
   92        ['haxe']:
   93                ("static",ws_,"inline",ws_,"var",ws_,Name,ws,"=",ws,Value),
   94        ['java','dart']:
   95                ("final",ws_,Type,ws_,Name,ws,"=",ws,Value),
   96        ['c']:
   97				("static",ws_,"const",ws_,Name,ws,"=",ws,Value),
   98        ['chapel']:
   99                ("var",ws_,Name,ws,":",ws,Type,ws,"=",ws,Value),
  100        ['typescript']:
  101                ("const",ws_,Name,ws,":",ws,Type,ws,"=",ws,Value)
  102		]).
  103
  104set_array_size_(Data,[Name,Size,Type]) -->
  105		langs_to_output(Data,set_array_size,[
  106		['scala']:
  107                ("var",ws_,Name,ws,"=",ws,"Array",ws,".",ws,"fill",ws,"(",ws,Size,ws,")",ws,"{",ws,"0",ws,"}"),
  108        ['octave']:
  109                (Name,ws,"=",ws,"zeros",ws,"(",ws,Size,ws,")"),
  110        ['minizinc']:
  111                ("array",ws,"[",ws,"1",ws,"..",ws,Size,ws,"]",ws_,"of",ws_,Type,ws,":",ws,Name,ws,";"),
  112        ['dart']:
  113                ("List",ws_,Name,ws,"=",ws,"new",ws_,"List",ws,"(",ws,Size,ws,")"),
  114        ['java','c#']:
  115                (Type,ws,"[]",ws_,Name,ws,"=",ws,"new",ws_,Type,ws,"[",ws,Size,ws,"]"),
  116        ['fortran']:
  117                (Type,ws,"(",ws,"LEN",ws,"=",ws,Size,ws,")",ws,"",ws,"::",ws,Name),
  118        ['go']:
  119                ("var",ws_,Name,ws_,"[",ws,Size,ws,"]",ws,Type),
  120        ['swift']:
  121                ("var",ws_,Name,ws,"=",ws,"[",ws,Type,ws,"]",ws,"(",ws,"count:",ws,Size,ws,",",ws,"repeatedValue",ws,":",ws,"0",ws,")"),
  122        ['c','c++']:
  123                (Type,ws_,Name,ws,"[",ws,Size,ws,"]"),
  124        ['rebol']:
  125                (Name,ws,":",ws,"array",ws_,Size),
  126        ['php']:
  127                (Name,ws,"=",ws,"array_fill",ws,"(",ws,"0",ws,",",ws,Size,ws,",",ws,"0",ws,")"),
  128        ['haxe']:
  129                ("var",ws_,"vector",ws,"=",ws,"",ws_,"haxe",ws,".",ws,"ds",ws,".",ws,"Vector",ws,"(",ws,Size,ws,")"),
  130        ['javascript']:
  131                ("var",ws_,Name,ws,"=",ws,"Array",ws,".",ws,"apply",ws,"(",ws,"null",ws,",",ws,"Array",ws,"(",ws,Size,ws,")",ws,")",ws,".",ws,"map",ws,"(",ws,"function",ws,"(",ws,")",ws,"{",ws,"}",ws,")"),
  132        ['vbscript']:
  133                ("Dim",ws_,Name,ws,"(",ws,Size,ws,")")
  134        ]).
  135        
  136set_var_(Data,[Name,Value]) -->
  137	langs_to_output(Data,set_var,[
  138	['sympy']:
  139			("Eq",ws,"(",ws,Name,ws,",",ws,Value,ws,")"),
  140    ['javascript','systemverilog','elixir','visual basic .net','lua','ruby','scriptol','mathematical notation','perl 6','wolfram','chapel','katahdin','frink','picat','ooc','d','genie','janus','ceylon','idp','processing','java','boo','gosu','pike','kotlin','icon','powershell','engscript','pawn','freebasic','hack','nim','openoffice basic','groovy','typescript','rust','fortran','awk','go','swift','vala','c','julia','scala','cobra','erlang','autoit','dart','java','ocaml','haxe','c#','matlab','c++','php','perl','gambas','octave','visual basic','bc']:
  141			(Name,ws,"=",ws,Value),
  142	['python','cython','coffeescript','haskell']:
  143			(Name,python_ws,"=",python_ws,Value),
  144	['english_temp']:
  145			(Name,python_ws,"=",python_ws,Value),
  146	['csh']:
  147			("@",ws,Name,ws,"=",ws,Value),
  148	%depends on the type of Value
  149	['prolog','constraint handling rules']:
  150			(Name,ws,"=",ws,Value),
  151	['hy']:
  152			("(",ws,"setv",ws_,Name,ws_,Value,ws,")"),
  153	['minizinc']:
  154			("constraint",ws_,Name,ws,"=",ws,Value),
  155	['rebol']:
  156			(Name,ws,":",ws,Value),
  157	['z3']:
  158			("(",ws,"assert",ws,"(",ws,"=",ws_,Name,ws_,Value,ws,")",ws,")"),
  159	['gap','seed7','delphi','vhdl']:
  160			(Name,ws,":=",ws,Value),
  161	['r']:
  162			(Name,ws,"<-",ws,Value),
  163	['livecode']:
  164			("put",ws_,"expression",ws_,"into",ws_,Name),
  165	['vbscript']:
  166			("Set",ws_,"a",ws,"=",ws,"b")
  167	]).
  168
  169initialize_instance_var_(Data,[Type,Name]) -->
  170	langs_to_output(Data,initialize_instance_var,[
  171		['java','c#']:
  172			("private",ws_,Type,ws_,Name,ws,";"),
  173		['php']:
  174			("private",ws_,Name,ws,";"),
  175		['javascript','perl']:
  176			"",
  177		['haxe','swift']:
  178			initialize_empty_var_(Data,[Name,Type])
  179	]).
  180	
  181initialize_instance_var_with_value_(Data,[Name,Expr,Type]) -->
  182	langs_to_output(Data,initialize_instance_var_with_value,[
  183		['java','c#']:
  184			("private",ws_,Type,ws_,Name,ws,"=",ws,Expr,ws,";"),
  185		['php']:
  186			("private",ws_,Name,ws,"=",ws,Expr,ws,";"),
  187		['javascript','perl']:
  188			"",
  189		['haxe','swift']:
  190			initialize_var_(Data,[Name,Expr,Type])
  191	]).
  192
  193initialize_reference_(Data,[Name,Expr,Type]) -->	
  194	langs_to_output(Data,initialize_reference,[
  195	['c++']:
  196		(Type,ws_,"&",ws_,Name,ws_,"=",ws_,Expr)
  197]).
  198
  199initialize_var_(Data,[Name,Expr,Type]) -->
  200	{Data = [Lang|_]},
  201	langs_to_output(Data,initialize_var,[
  202	['polish notation']:
  203        ("=",ws_,Name,ws_,Expr),
  204    ['visual basic','visual basic .net','openoffice basic']:
  205			("Dim",ws_,Name,ws_,"As",ws_,Type,ws,"=",ws,Expr),
  206    ['hy']:
  207        ("(",ws,"setv",ws_,Name,ws_,Expr,ws,")"),
  208    ['reverse polish notation']:
  209        (Name,ws_,Expr,ws_,"="),
  210    ['go']:
  211        ("var",ws_,Name,ws_,Type,ws,"=",ws,Expr),
  212    ['rust']:
  213        ("let",ws_,"mut",ws_,Name,ws,"=",ws,Expr),
  214    ['pseudocode','dafny']:
  215        ("var",ws,Name,ws,":",ws,Type,ws,":=",ws,Expr),
  216    ['gnu smalltalk']:
  217        (Name,ws_,":=",ws_,Expr),
  218    ['z3']:
  219        ("(",ws,"declare-const",ws_,Name,ws_,Type,ws,")",ws,"(",ws,"assert",ws_,"(",ws,"=",ws_,Name,ws_,Expr,ws,")",ws,")"),
  220    ['f#']:
  221        ("let",ws_,"mutable",ws_,Name,ws,"=",ws,Expr),
  222    ['common lisp']:
  223        ("(",ws,"setf",ws_,Name,ws_,Expr,ws,")"),
  224    ['minizinc']:
  225        (Type,ws,":",ws,Name,ws,"=",ws,Expr),
  226    ['ruby','erlang','php','prolog','constraint handling rules','logtalk','picat','octave','wolfram']:
  227        (Name,ws,"=",ws,Expr),
  228    ['python','cython','haskell','julia']:
  229        (Name,python_ws,"=",python_ws,Expr),
  230    ['javascript','hack','swift']:
  231        ("var",ws_,Name,ws,"=",ws,Expr),
  232    ['pseudocode','lua','gap','bash']:
  233        ("local",ws_,Name,ws,"=",ws,Expr),
  234    ['pseudocode','janus']:
  235        ("local",ws_,Type,ws_,Name,ws,"=",ws,Expr),
  236    ['pseudocode','perl']:
  237        ("my",ws_,Name,ws,"=",ws,Expr),
  238    ['pseudocode','perl 6']:
  239        ("my",ws_,Type,ws_,Name,ws,"=",ws,Expr),
  240    ['pseudocode','systemverilog','java','scriptol','c','cosmos','c++','d','dart','englishscript','ceylon']:
  241		(Type,ws_,Name,ws,"=",ws,Expr),
  242    ['pseudocode','c#','vala']:
  243        ((Type;"var"),ws_,Name,ws,"=",ws,Expr),
  244    ['rebol']:
  245        (Name,ws,":",ws,Expr),
  246    ['r']:
  247        (Name,ws,"<-",ws,Expr),
  248    ['pseudocode','fortran']:
  249        (Type,ws,"::",ws,Name,ws,"=",ws,Expr),
  250    ['pseudocode','chapel','haxe','scala','typescript']:
  251        ("var",ws_,Name,(ws,":",Type,ws;ws),"=",ws,Expr),
  252    ['monkey x']:
  253        ("Local",ws_,Name,ws,":",ws,Type,ws,"=",ws,Expr),
  254    ['vbscript']:
  255        ("Dim",ws_,Name,ws_,"Set",ws_,Name,ws,"=",ws,Expr),
  256    ['pseudocode','seed7']:
  257        ("var",ws_,Type,ws,":",ws,Name,ws_,"is",ws_,Expr),
  258    ['python']:
  259		(Name,python_ws,"=",python_ws,Expr)
  260	]).
  261
  262index_in_array_(Data,[Container,Contained]) -->
  263    langs_to_output(Data,index_in_array,[
  264    ['javascript']:
  265        (Container,ws,".",ws,"indexOf",ws,"(",ws,Contained,ws,")"),
  266    ['ruby']:
  267        (Container,ws,".",ws,"index",ws,"(",ws,Contained,ws,")"),
  268    ['perl']:
  269        ("firstidx",ws,"{",ws,"$_",ws_,"eq",ws_,Contained,ws,"}",ws,Container),
  270    ['php']:
  271        ("array_search",ws,"(",ws,Contained,ws,",",ws,Container,ws,")"),
  272    ['c#']:
  273        ("Array",ws,".",ws,"IndexOf",ws,"(",ws,Container,ws,",",ws,Contained,ws,")"),
  274    ['cython']:
  275        (Container,python_ws,".",python_ws,"index",python_ws,"(",python_ws,Contained,python_ws,")"),
  276    ['english_temp']:
  277		(optional_the("first"),python_ws_,("occurrence";"appearance"),python_ws_,"of",python_ws_,Contained,python_ws_,"in",python_ws_,Container)
  278    ]).
  279
  280
  281% https://www.rosettacode.org/wiki/Remove_duplicate_elements
  282remove_duplicates(Data,[A]) -->
  283	langs_to_output(Data,remove_duplicates,[
  284		['php']:
  285			("array_unique",ws,"(",ws,A,ws,")"),
  286		['python']:
  287			("unique_everseen",python_ws,"(",python_ws,A,python_ws,")"),
  288		['ruby']:
  289			(A,ws,".",ws,"uniq"),
  290		['c#']:
  291			(A,ws,".",ws,"Distinct",ws,"(",ws,")",ws,".",ws,"ToArray",ws,"(",ws,")"),
  292		['clojure']:
  293			("(",ws,"distinct",ws_,A,ws,")"),
  294		['english_temp']:
  295			(A,python_ws_,"without",python_ws_,"duplicates")
  296	]).
  297
  298remove_duplicates_in_place(Data,[A]) -->
  299	langs_to_output(Data,remove_duplicates,[
  300		['ruby']:
  301			(A,ws,".",ws,"uniq!")
  302	]).
  303
  304expr(Data,Type,arithmetic(Exp1,Exp2,Symbol)) -->
  305        {
  306                member(Symbol,["+","-","*","/"])
  307        },
  308        arithmetic_(Data,[
  309			dot_expr(Data,Type,Exp1),
  310			expr(Data,Type,Exp2),
  311			Symbol
  312		]),{Type=int;Type=double}.
  313
  314concatenate_string_(Data,[A,B]) -->
  315        langs_to_output(Data,concatenate_string,[
  316        ['prolog','constraint handling rules']:
  317				("(",ws,"append",ws_,"$(",ws,A,ws,",",ws,B,ws,")",ws,")"),
  318        ['r']:
  319                ("paste0",ws,"(",ws,A,ws,",",ws,B,ws,")"),
  320        ['maxima']:
  321                ("sconcat",ws,"(",ws,A,ws,",",ws,B,ws,")"),
  322        ['common lisp']:
  323                ("(",ws,"concatenate",ws_,"'string",ws_,A,ws_,B,ws,")"),
  324        ['c','ruby','python','cosmos','z3py','monkey x','englishscript','mathematical notation','go','java','chapel','frink','freebasic','nemerle','d','cython','ceylon','coffeescript','typescript','dart','gosu','groovy','scala','swift','f#','javascript','c#','haxe','c++','vala']:
  325                (A,python_ws,"+",python_ws,B),
  326		['english']:
  327                (A,python_ws,"+",python_ws,B),
  328        ['engscript','lua']:
  329                (A,ws,"..",ws,B),
  330        ['fortran']:
  331                (A,ws,"//",ws,B),
  332        ['php','autohotkey','hack','perl']:
  333                (A,ws,".",ws,B),
  334        ['ocaml']:
  335                (A,ws,"^",ws,B),
  336        ['rebol']:
  337                ("append",ws_,A,ws_,B),
  338        ['haskell','minizinc','picat','elm']:
  339                (A,ws,"++",ws,B),
  340        ['clips']:
  341                ("(",ws,"str-cat",ws_,A,ws_,B,ws,")"),
  342        ['clojure']:
  343                ("(",ws,"str",ws_,A,ws_,B,ws,")"),
  344        ['erlang']:
  345                ("string",ws,":",ws,"concat",ws,"(",ws,A,ws,",",ws,B,ws,")"),
  346        ['julia']:
  347                ("string",ws,"(",ws,A,ws,",",ws,B,ws,")"),
  348        ['octave']:
  349                ("strcat",ws,"(",ws,A,ws,",",ws,B,ws,")"),
  350        ['racket']:
  351                ("(",ws,"string-append",ws,A,ws,B,ws,")"),
  352        ['delphi']:
  353                ("Concat",ws,"(",ws,A,ws,",",ws,B,ws,")"),
  354        ['visual basic','seed7','visual basic .net','gambas','nim','autoit','openoffice basic','livecode','vbscript']:
  355                (A,ws,"&",ws,B),
  356        ['elixir','wolfram','purescript']:
  357                (A,ws,"<>",ws,B),
  358        ['perl 6']:
  359                (A,ws,"~",ws,B),
  360        ['z3']:
  361                ("(",ws,"Concat",ws_,A,ws_,B,ws,")"),
  362        ['emacs lisp']:
  363                ("(",ws,"concat",ws_,A,ws_,B,ws,")"),
  364        ['polish notation']:
  365                ("+",ws_,A,ws_,B),
  366        ['reverse polish notation']:
  367                (A,ws_,B,ws_,"+")
  368        ]).
  369
  370array_length(Data,[A])-->
  371        langs_to_output(Data,array_length,[
  372        ['go']:
  373                ("len",ws,"(",ws,A,ws,")"),
  374		['prolog','constraint handling rules']:
  375				("(",ws,"length",ws_,"$",ws,A,ws,")",ws,")"),
  376        ['python','cython']:
  377                ("len",python_ws,"(",python_ws,A,python_ws,")"),
  378        ['java','picat','scala','d','typescript','dart','vala','javascript','haxe','cobra','ruby']:
  379                (A,ws,".",ws,"length"),
  380		['coffeescript']:
  381                (A,ws,".",ws,"length"),
  382        ['c#','visual basic','powershell','visual basic .net']:
  383                (A,ws,".",ws,"Length"),
  384        ['minizinc','julia','r']:
  385                ("length",ws,"(",ws,A,ws,")"),
  386        ['common lisp']:
  387                ("(",ws,"list-length",ws_,A,ws,")"),
  388        ['php']:
  389                ("count",ws,"(",ws,A,ws,")"),
  390        ['rust']:
  391                (A,ws,".",ws,"len",ws,"(",ws,")"),
  392        ['emacs lisp','scheme','racket','haskell']:
  393                ("(",ws,"length",ws_,A,ws,")"),
  394        ['c++','groovy']:
  395                (A,ws,".",ws,"size",ws,"(",ws,")"),
  396        ['c']:
  397                ("sizeof",ws,"(",ws,A,ws,")",ws,"/",ws,"sizeof",ws,"(",ws,A,ws,"[",ws,"0",ws,"]",ws,")"),
  398        ['perl']:
  399                ("scalar",ws,"(",ws,A,ws,")"),
  400        ['rebol']:
  401                ("length?",ws_,A),
  402        ['swift']:
  403                (A,ws,".",ws,"count"),
  404        ['clojure']:
  405                ("(",ws,"count",ws_,"array",ws,")"),
  406        ['hy']:
  407                ("(",ws,"len",ws_,A,ws,")"),
  408        ['octave','seed7']:
  409                ("length",ws,"(",ws,A,ws,")"),
  410        ['fortran','janus']:
  411                ("size",ws,"(",ws,A,ws,")"),
  412        ['wolfram']:
  413                ("Length",ws,"[",ws,A,ws,"]"),
  414        ['english_temp']:
  415				(
  416					optional_the("length"),python_ws_,"of",python_ws_,A;
  417					A,"'s",ws_,"length"
  418				)
  419        ]).
  420
  421strlen_(Data,[A]) -->
  422        langs_to_output(Data,strlen,[
  423		['prolog','constraint handling rules']:
  424				("(",ws,"length",ws_,"$",ws,A,ws,")",ws,")"),
  425        ['go','erlang','nim','python']:
  426                ("len",python_ws,"(",python_ws,A,python_ws,")"),
  427        ['lua']:
  428                ("string",ws,".",ws,"length",ws,"(",ws,A,ws,")"),
  429        ['r']:
  430                ("nchar",ws,"(",ws,A,ws,")"),
  431        ['erlang']:
  432                ("string:len",ws,"(",ws,A,ws,")"),
  433        ['visual basic','gambas']:
  434                ("Len",ws,"(",ws,A,ws,")"),
  435        ['javascript','typescript','scala','gosu','picat','haxe','ocaml','d','dart']:
  436                (A,ws,".",ws,"length"),
  437        ['rebol']:
  438                ("length?",ws_,A),
  439        ['java','c++','kotlin']:
  440                (A,ws,".",ws,"length",ws,"(",ws,")"),
  441        ['systemverilog']:
  442				(Str,ws,".",ws,"len",ws,"(",ws,")"),
  443        ['php','c','pawn','hack']:
  444                ("strlen",ws,"(",ws,A,ws,")"),
  445        ['minizinc','julia','perl','seed7','octave']:
  446                ("length",ws,"(",ws,A,ws,")"),
  447        ['c#','nemerle']:
  448                (A,ws,".",ws,"Length"),
  449        ['swift']:
  450                ("countElements",ws,"(",ws,A,ws,")"),
  451        ['autoit']:
  452                ("StringLen",ws,"(",ws,A,ws,")"),
  453        ['common lisp','haskell']:
  454                ("(",ws,"length",ws_,A,ws,")"),
  455        ['racket','scheme']:
  456                ("(",ws,"string-length",ws_,A,ws,")"),
  457        ['fortran']:
  458                ("LEN",ws,"(",ws,A,ws,")"),
  459        ['wolfram']:
  460                ("StringLength",ws,"[",ws,A,ws,"]"),
  461        ['z3']:
  462                ("(",ws,"Length",ws_,A,ws,")"),
  463        ['english_temp']:
  464				(
  465					optional_the("length"),python_ws_,"of",python_ws_,A;
  466					A,"'s",ws_,"length"
  467				)
  468        ]).
  469
  470access_array_(Data,[Array,Index]) -->
  471        langs_to_output(Data,access_array,[
  472        ['prolog','constraint handling rules']:
  473				("(",ws,"nth0",ws_,"$",ws,"(",ws,Array,ws,",",ws,Index,ws,")",ws,")"),
  474        ['ruby','c#','julia','d','swift','julia','janus','minizinc','picat','nim','autoit','python_temp','cython','coffeescript','dart','typescript','awk','vala','perl','java','javascript','go','c++','php','haxe','c']:
  475                (Array,python_ws,"[",python_ws,Index,python_ws,"]"),
  476		['lua']:
  477				(Array,ws,"[",ws,Index,ws,"+",ws,"1",ws,"]"),
  478        ['scala','octave','fortran','visual basic','visual basic .net']:
  479                (Array,ws,"(",ws,Index,ws,")"),
  480        ['haskell']:
  481                ("(",ws,Array,ws,"!!",ws,Index,ws,")"),
  482        ['frink']:
  483                (Array,ws,"@",ws,Index),
  484        ['z3']:
  485                ("(",ws,"select",ws_,Array,ws_,Index,ws,")"),
  486        ['rebol']:
  487                (Array,ws,"/",ws,Index)
  488        ]).
  489
  490%not reversed in place
  491%list backwards
  492reverse_list_(Data,[List]) -->
  493        langs_to_output(Data,reverse_list,[
  494			['php']:
  495				("array_reverse",ws,"(",ws,List,ws,")"),
  496			['perl']:
  497				("reverse",ws,"(",ws,List,ws,")"),
  498			['ruby']:
  499				(List,ws,".",ws,"reverse"),
  500			['python','cython']:
  501				(List,python_ws,"[::-1]";"reversed",ws,"(",ws,List,ws,")"),
  502			['english_temp']:
  503				(List,python_ws_,"reversed"),
  504			['haskell']:
  505				("(",ws,"reverse",ws_,List,ws,")"),
  506			['ocaml']:
  507				("(",ws,"List.rev",ws_,List,ws,")"),
  508			['javascript']:
  509				(List,ws,".",ws,"map",ws,"(",ws,"function",ws,"(",ws,"arr",ws,")",ws,"{",ws,"return",ws_,"arr",ws,".",ws,"slice()",ws,";",ws,"}",ws,")")
  510		]).
  511
  512reverse_list_in_place_(Data,[List]) -->
  513        langs_to_output(Data,reverse_list_in_place,[
  514			['javascript','python']:
  515				(List,python_ws,".",python_ws,"reverse",python_ws,"(",python_ws,")"),
  516			['ruby']:
  517				(List,python_ws,".",python_ws,"reverse!"),
  518			['english_temp']:
  519				("reverse",ws_,List),
  520			['php']:
  521				set_var_(Data,[List,reverse_list_(Data,[List])]),
  522			['java']:
  523				("Collections",ws,".",ws,"reverse(",ws,List,ws,")")
  524		]).
  525
  526charAt_(Data,[AString,Index]) -->
  527        langs_to_output(Data,charAt,[
  528        ['english_temp']:
  529				(optional_the(Index),("st";"nd";"rd";"th"),python_ws_,"character",python_ws_,("in";"of"),python_ws_,AString),
  530        ['java','haxe','scala','javascript','typescript']:
  531                (AString,ws,".",ws,"charAt",ws,"(",ws,Index,ws,")"),
  532        ['z3']:
  533                ("(",ws,"CharAt",ws_,"expression",ws_,Index,ws,")"),
  534        ['c','php','c#','minizinc','c++','picat','haskell','dart']:
  535                (AString,ws,"[",ws,Index,ws,"]"),
  536        ['python','english_temp']:
  537                (AString,python_ws,"[",python_ws,Index,python_ws,"]"),
  538        ['octave']:
  539                (AString,ws,"(",ws,Index,ws,")"),
  540        ['chapel']:
  541                (AString,ws,".",ws,"substring",ws,"(",ws,Index,ws,")"),
  542        ['go']:
  543                ("string",ws,"(",ws,"[",ws,"]",ws,"rune",ws,"(",ws,AString,ws,")",ws,"[",ws,Index,ws,"]",ws,")"),
  544        ['swift']:
  545                (AString,ws,"[",ws,AString,ws,".",ws,"startIndex",ws,".",ws,"advancedBy",ws,"(",ws,Index,ws,")",ws,"]"),
  546        ['rebol']:
  547                (AString,ws,"/",ws,Index),
  548        ['perl']:
  549                ("substr",ws,"(",ws,AString,ws,",",ws,Index,ws,"-",ws,"1",ws,",",ws,"1",ws,")")
  550        ]).
  551
  552join_(Data,[Array,Separator]) -->
  553        langs_to_output(Data,join,[
  554        ['prolog','constraint handling rules']:
  555				("(",ws,"join",ws_,"$(",ws,Array,ws,",",ws,Separator,ws,")",")"),
  556        ['swift']:
  557                (Array,ws,".",ws,"joinWithSeparator",ws,"(",ws,Separator,ws,")"),
  558        ['c#']:
  559                ("String",ws,".",ws,"Join",ws,"(",ws,Separator,ws,",",ws,Array,ws,")"),
  560        ['php']:
  561                ("implode",ws,"(",ws,Separator,ws,",",ws,Array,ws,")"),
  562        ['perl']:
  563                ("join",ws,"(",ws,Separator,ws,",",ws,Array,ws,")"),
  564        ['d','julia']:
  565                ("join",ws,"(",ws,Array,ws,",",ws,Separator,ws,")"),
  566        ['go']:
  567                ("Strings",ws,".",ws,"join",ws,"(",ws,Array,ws,",",ws,Separator,ws,")"),
  568        ['javascript','haxe','groovy','java','typescript','rust','dart','ruby']:
  569                (Array,ws,".",ws,"join",ws,"(",ws,Separator,ws,")"),
  570		['coffeescript']:
  571                (Array,python_ws,".",python_ws,"join",python_ws,"(",python_ws,Separator,python_ws,")"),
  572        ['scala']:
  573                (Array,ws,".",ws,"mkString",ws,"(",ws,Separator,ws,")")
  574        ]).
  575
  576%Concatenate arrays, not in-place
  577concatenate_arrays_(Data,[A1,A2]) -->
  578        langs_to_output(Data,concatenate_arrays,[
  579        ['prolog','constraint handling rules']:
  580				("(",ws,"append",ws_,"$(",ws,A1,ws,",",ws,A2,ws,")"),
  581        ['javascript','typescript','haxe']:
  582                (A1,ws,".",ws,"concat",ws,"(",ws,A2,ws,")"),
  583        ['haskell']:
  584                (A1,ws,"++",ws,A2),
  585        ['go']:
  586                ("append",ws,"(",ws,A1,ws,",",ws,A2,ws,")"),
  587        ['cython','python','ruby','swift']:
  588                (A1,python_ws,"+",python_ws,A2),
  589        ['d']:
  590                (A1,python_ws,"~",python_ws,A2),
  591        ['perl']:
  592                ("push",ws,"(",ws,A1,ws,",",ws,A2,ws,")"),
  593        ['r']:
  594                ("c",ws,"(",ws,A1,ws,",",ws,A2,ws,")"),
  595        ['php']:
  596                ("array_merge",ws,"(",ws,A1,ws,",",ws,A2,ws,")"),
  597        [hy]:
  598                ("(",ws,"+",ws_,A1,ws_,A2,ws,")"),
  599        ['c#']:
  600                (A1,ws,".",ws,"concat",ws,"(",ws,A2,ws,")",ws,".",ws,"ToArray",ws,"(",ws,")")
  601        ]).
  602
  603split_(Data,[AString,Separator]) -->
  604    langs_to_output(Data,split,[
  605    ['prolog','constraint handling rules']:
  606			("(",ws,"split",ws_,"$(",ws,AString,ws,",",ws,Separator,ws,")",ws,")"),
  607    ['swift']:
  608            (AString,ws,".",ws,"componentsSeparatedByString",ws,"(",ws,Separator,ws,")"),
  609    ['octave']:
  610            ("strsplit",ws,"(",ws,AString,ws,",",ws,Separator,ws,")"),
  611    ['go']:
  612            ("strings",ws,".",ws,"Split",ws,"(",ws,AString,ws,",",ws,Separator,ws,")"),
  613    ['javascript','ruby','coffeescript','java','dart','scala','groovy','haxe','rust','typescript','python','cython','vala']:
  614            (AString,python_ws,".",python_ws,"split",python_ws,"(",python_ws,Separator,python_ws,")"),
  615    ['php']:
  616            ("explode",ws,"(",ws,Separator,ws,",",ws,AString,ws,")"),
  617    ['perl','processing']:
  618            ("split",ws,"(",ws,Separator,ws,",",ws,AString,ws,")"),
  619    ['rebol']:
  620            ("split",ws_,AString,ws_,Separator),
  621    ['c#']:
  622            (AString,ws,".",ws,"Split",ws,"(",ws,"new",ws,"string[]",ws,"{",ws,Separator,ws,"}",ws,",",ws,"StringSplitOptions",ws,".",ws,"None",ws,")"),
  623    ['picat','d','julia']:
  624            ("split",ws,"(",ws,AString,ws,",",ws,Separator,ws,")"),
  625    ['haskell']:
  626            ("(",ws,"splitOn",ws_,AString,ws_,Separator,ws,")"),
  627    ['wolfram']:
  628            ("StringSplit",ws,"[",ws,AString,ws,",",ws,Separator,ws,"]")
  629    ]).
  630
  631function_call_(Data,[Name,Args]) -->
  632	langs_to_output(Data,function_call,[
  633    ['c','english_temp','sympy','lua','cython','definite clause grammars','python','ruby','logtalk','nim','seed7','gap','mathematical notation','chapel','elixir','janus','perl 6','pascal','rust','hack','katahdin','minizinc','pawn','aldor','picat','d','genie','ooc','pl/i','delphi','standard ml','rexx','falcon','idp','processing','maxima','swift','boo','r','matlab','autoit','pike','gosu','awk','autohotkey','gambas','kotlin','nemerle','engscript','groovy','scala','coffeescript','julia','typescript','fortran','octave','c++','go','cobra','vala','f#','java','ceylon','erlang','c#','haxe','javascript','dart','bc','visual basic','php','perl']:
  634			(Name,python_ws,"(",python_ws,Args,python_ws,")"),
  635	['prolog','constraint handling rules']:
  636			("(",ws,Name,ws_,"$",ws,"(",Args,")",ws,")"),
  637	['haskell','ocaml','z3','clips','clojure','common lisp','clips','racket','scheme','rebol']:
  638			("(",ws,Name,ws_,Args,ws,")"),
  639	['polish notation']:
  640			(Name,ws_,Args),
  641	['reverse polish notation']:
  642			(Args,ws_,Name),
  643	['pydatalog','nearley']:
  644			(Name,ws,"[",ws,Args,ws,"]"),
  645	['hy']:
  646			("(",ws,Name,ws_,Args,ws,")"),
  647	['peg.js']:
  648			(Args,ws,":",ws,Name),
  649	['antlr','abnf','marpa','waxeye','parboiled','wirth syntax notation']:
  650			Name,
  651	['lpeg']:
  652			("lpeg.V\"",Name,"\"")
  653    ]).
  654
  655minus_minus_(Data,[Name]) -->
  656        langs_to_output(Data,minus_minus,[
  657        ["javascript","php","kotlin","haxe","scala","java","c","c++","c#","perl","go"]:
  658			(Name,ws,"--"),
  659		['ruby']:
  660			(Name,ws,"=",ws,Name,ws,"-",ws,"1")
  661		]).
  662
  663initialize_static_var_with_value_(Data,[Type,Name,Value]) -->
  664    	langs_to_output(Data,initialize_static_var_with_value,[
  665		['polish notation']:
  666			("=",ws_,Name,ws_,Value),
  667		['reverse polish notation']:
  668			(Name,ws_,Value,ws_,"="),
  669		['go']:
  670			("var",ws_,Name,ws_,Type,ws,"=",ws,Value),
  671		['rust']:
  672			("let",ws_,"mut",ws_,Name,ws,"=",ws,Value),
  673		['dafny']:
  674			("var",ws,Name,ws,":",ws,Type,ws,":=",ws,Value),
  675		['z3']:
  676			("(",ws,"declare-const",ws_,Name,ws_,Type,ws,")",ws,"(",ws,"assert",ws_,"(",ws,"=",ws_,Name,ws_,Value,ws,")",ws,")"),
  677		['f#']:
  678			("let",ws_,"mutable",ws_,Name,ws,"=",ws,Value),
  679		['common lisp']:
  680			("(",ws,"setf",ws_,Name,ws_,Value,ws,")"),
  681		['minizinc']:
  682			(Type,ws,":",ws,Name,ws,"=",ws,Value,ws,";"),
  683		['haskell','erlang','prolog','constraint handling rules','julia','picat','octave','wolfram']:
  684			(Name,ws,"=",ws,Value),
  685		['javascript','hack','swift']:
  686			("var",ws_,Name,ws,"=",ws,Value),
  687		['janus']:
  688			("local",ws_,Type,ws_,Name,ws,"=",ws,Value),
  689		['perl']:
  690			("my",ws_,Name,ws,"=",ws,Value),
  691		['perl 6']:
  692			("my",ws_,Type,ws_,Name,ws,"=",ws,Value),
  693		['c','java','c#','c++','d','dart','englishscript','ceylon','vala']:
  694			(Type,ws_,Name,ws,"=",ws,Value),
  695		['rebol']:
  696			(Name,ws,":",ws,Value),
  697		['visual basic','visual basic .net','openoffice basic']:
  698			("Dim",ws_,Name,ws_,"As",ws_,Type,ws,"=",ws,Value),
  699		['r']:
  700			(Name,ws,"<-",ws,Value),
  701		['fortran']:
  702			(Type,ws,"::",ws,Name,ws,"=",ws,Value),
  703		['chapel','haxe','scala','typescript']:
  704			("var",ws_,Name,ws,":",ws,Type,ws,"=",ws,Value),
  705		['monkey x']:
  706			("Local",ws_,Name,ws,":",ws,Type,ws,"=",ws,Value),
  707		['vbscript']:
  708			("Dim",ws_,Name,ws_,"Set",ws_,Name,ws,"=",ws,Value),
  709		['seed7']:
  710			("var",ws_,Type,ws,":",ws,Name,ws_,"is",ws_,Value)
  711        ]).
  712
  713private_instance_method_(Data,[Name,Type,Params,Body,Indent]) -->
  714		langs_to_output(Data,private_instance_method,[
  715			['java','c#']:
  716					("private",ws_,Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",!,ws,Body,(Indent;ws),"}"),
  717			['php']:
  718					("private",ws_,"function",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",!,ws,Body,(Indent;ws),"}")
  719		]).
  720
  721instance_method_(Data,[Name,Type,Params,Body,Indent]) -->
  722		langs_to_output(Data,instance_method,[
  723		['hy']:
  724			("(",ws,"defn",ws_,Name,ws_,"[",ws,"self",ws_,Params,ws,"]",ws_,Body,ws,")"),
  725		['python','cython']:
  726				("def",python_ws_,Name,"(",python_ws,"self",python_ws,",",Params,")",":",python_ws,Body),
  727		['swift']:
  728                ("func",ws_,Name,ws,"(",ws,Params,ws,")",ws,"->",ws,Type,ws,"{",!,ws,Body,(Indent;ws),"}"),
  729        [logtalk]:
  730                (Name,ws,"(",ws,Params,ws,",",ws,"Return",ws,")",ws_,":-",ws_,Body),
  731        ['ruby']:
  732                ("def",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Body,(Indent;ws_),"end"),
  733        ['perl']:
  734                ("sub",ws_,Name,ws,"{",ws,"my",ws,"(",Params,")",ws,"=@_",ws,";",ws,Body,(Indent;ws),"}"),
  735        ['javascript']:
  736                (Name,ws,"(",ws,Params,ws,")",ws,"{",!,ws,Body,(Indent;ws),"}"),
  737        ['perl 6']:
  738                ("method",ws_,Name,ws_,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  739        ['chapel']:
  740                ("def",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
  741        ['java','c#']:
  742                ("public",ws_,Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  743        ['php']:
  744                ("public",ws_,"function",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  745        ['c++','d','dart']:
  746                (Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  747        ['haxe']:
  748                ("public",ws_,"function",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,"{",ws,Body,(Indent;ws),"}")
  749        ]).
  750
  751static_method_(Data, [Name,Type,Params,Body,Indent]) -->        
  752        langs_to_output(Data,static_method,[
  753        ['swift','pseudocode']:
  754                ("class",ws_,"func",ws_,Name,ws,"(",ws,Params,ws,")",ws,"->",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
  755        ['perl']:
  756                ("sub",ws_,Name,ws,"{",ws,"my",ws,"(",Params,")",ws,"=@_",ws,";",ws,Body,(Indent;ws),"}"),
  757        ['haxe','pseudocode']:
  758                ("public",ws_,"static",ws_,"function",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  759        ['julia']:
  760                ("function",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Body,(Indent;ws_),"end"),
  761        ['java','c#','pseudocode']:
  762                ("public",ws_,"static",ws_,Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  763        ['c++','dart','pseudocode']:
  764                ("static",ws_,Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  765        ['php','pseudocode']:
  766                ("public",ws_,"static",ws_,"function",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  767        ['c']:
  768                (Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  769        ['javascript','typescript','pseudocode']:
  770                ("static",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  771        ['python_temp']:
  772				("@staticmethod",Indent,"def",python_ws,"(",python_ws,Params,python_ws,")",":",python_ws,Statements),
  773        ['picat']:
  774                (ws)
  775        ]).
  776
  777
  778constructor_(Data,[Name,Params,Body,Indent]) -->
  779        langs_to_output(Data,constructor,[
  780        ['rebol']:
  781                ("new:",ws_,"func",ws,"[",ws,Params,ws,"]",ws,"[",ws,"make",ws_,"self",ws,"[",ws,Body,ws,"]",ws,"]"),
  782        ['hy']:
  783				("(",ws,"defn",ws_,"--init--",ws_,"[",ws,"self",ws_,Params,ws,"]",ws_,Body,ws,")"),
  784        ['java','c#','vala']:
  785                ("public",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  786        ['swift']:
  787                ("init",ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  788        ['javascript']:
  789                ("constructor",ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  790        ['php']:
  791                ("function",ws_,"__construct",ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  792        ['perl']:
  793                ("sub",ws_,"new",ws,"{",ws,"my($class,",Params,") = @_;my $s = {};bless $s, $class;",Body,"return $s;",(Indent;ws),"}"),
  794        ['haxe']:
  795                ("public",ws_,"function",ws_,"new",ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  796        ['c++','dart']:
  797                (Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  798        ['d']:
  799                ("this",ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  800        ['chapel']:
  801                ("proc",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
  802        ['julia']:
  803                ("function",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Body,(Indent;ws_),"end"),
  804        ['ruby']:
  805                ("def",ws_,"initialize",ws,"(",ws,Params,ws,")",ws_,Body,(Indent;ws_),"end")
  806        ]).
  807
  808plus_equals_(Data,[A,B]) -->
  809        langs_to_output(Data,plus_equals,[
  810        ['janus','python','coffeescript','visual basic','visual basic .net','nim','cython','vala','perl 6','dart','typescript','java','c','c++','c#','javascript','haxe','php','chapel','perl','julia','scala','rust','go','swift']:
  811                (A,python_ws,"+=",python_ws,B),
  812        ['english_temp']:
  813                (
  814					A,python_ws,"+=",python_ws,B;
  815					"add",python_ws,B,python_ws,"to",python_ws,A
  816				),
  817        ['haskell','ruby','lua','erlang','fortran','ocaml','minizinc','octave','delphi']:
  818                (A,ws,"=",ws,A,ws,"+",ws,B),
  819        ['haskell']:
  820                (A,python_ws,"<-",python_ws,A,python_ws,"+",python_ws,B),
  821        ['picat']:
  822                (A,ws,":=",ws,A,ws,"+",ws,B),
  823        ['rebol']:
  824                (A,ws,":",ws,A,ws,"+",ws,B),
  825        ['livecode']:
  826                ("add",ws_,B,ws_,"to",ws_,A),
  827        ['seed7']:
  828                (A,ws,"+:=",ws,B)
  829        ]).
  830
  831array_plus_equals_(Data,[A,B]) -->
  832        langs_to_output(Data,array_plus_equals,[
  833        ['python']:
  834			(A,python_ws,"+=",python_ws,B),
  835		['english_temp']:
  836			plus_equals_(Data,[A,B]),
  837		['perl']:
  838			("push",ws_,A,ws,",",ws_,B),
  839		['lua']:
  840			({unique_var(V)},"for",ws_,"_",ws,",",ws,V,ws_,"in",ws_,"pairs",ws,"(",ws,B,ws,")",ws_,"do",ws_,"table",ws,".",ws,"insert",ws,"(",ws,A,ws,",",ws,V,ws,")",ws_,"end"),
  841		['javascript']:
  842			(A,ws,".",ws,"push",ws,".",ws,"apply",ws,"(",ws,A,ws,",",ws,B,ws,")")
  843        ]).
  844
  845dict_plus_equals_(Data,[A,B]) -->
  846        langs_to_output(Data,dict_plus_equals,[
  847        ['python']:
  848			(A,python_ws,".",python_ws,"update",python_ws,"(",python_ws,B,")"),
  849		['lua']:
  850			("for",ws_,"k",ws,",",ws,"v",ws_,"in",ws_,"pairs",ws,"(",ws,B,ws,")",ws_,"do",ws_,A,ws,"[",ws,"k",ws,"]",ws,"=",ws,"v",ws_,"end"),
  851		['ruby']:
  852			(A,ws,"=",ws,A,ws,".",ws,"merge",ws,"(",ws,B,ws,")"),
  853		['php']:
  854			(A,ws,"=",ws,"array_merge",ws,"(",ws,A,ws,",",ws,B,ws,")"),
  855		['english_temp']:
  856			(A,python_ws,"+=",python_ws,B),
  857		['c#']:
  858			({unique_var(X)},B,ws,".",ws,"ToList",ws,"(",ws,")",ws,".",ws,"ForEach",ws,"(",ws,X,ws,"=>",ws,A,ws,".",ws,"Add",ws,"(",ws,X,ws,".",ws,"Key",ws,",",ws,X,ws,".",ws,"Value",ws,")",ws,")")
  859        ]).
  860
  861string_plus_equals_(Data,[A,B]) -->
  862	langs_to_output(Data,string_plus_equals,[
  863        ['python','java','javascript','c#']:
  864			(A,python_ws,"+=",python_ws,B),
  865		['english_temp']:
  866			plus_equals_(Data,[A,B]),
  867		['haskell']:
  868			(A,python_ws,"<-",python_ws,A,python_ws,"++",python_ws,B),
  869		['perl','php']:
  870			(A,ws,".=",ws,B),
  871		['ruby']:
  872			(A,ws,"<<",ws,B),
  873		['c++']:
  874			(A,ws,".",ws,"append",ws,"(",ws,B,ws,")"),
  875		['lua']:
  876			set_var_(Data,[A,concatenate_string_(Data,[A,B])])
  877    ]).
  878
  879divide_equals_(Data,[A,B]) -->
  880    langs_to_output(Data,divide_equals,[
  881	["javascript","java","c","c++","c#","perl","ruby","visual basic .net","php"]:
  882			(A,ws,"/=",ws,B),
  883	['python','coffeescript']:
  884			(A,python_ws,"/=",python_ws,B),
  885	['english_temp']:
  886			(
  887				A,python_ws,"/=",python_ws,B;
  888				"divide",python_ws_,A,python_ws_,"by",python_ws_,B
  889			)
  890    ]).
  891
  892modulo_equals_(Data,[A,B]) -->
  893    langs_to_output(Data,modulo_equals,[
  894	['c','c++','php','javascript','ruby','c#','java']:
  895			(A,ws,"%=",ws,B),
  896	['python']:
  897			(A,python_ws,"%=",python_ws,B)
  898    ]).
  899
  900exponent_equals_(Data,[A,B]) -->
  901    langs_to_output(Data,exponent_equals,[
  902	['perl','ruby']:
  903			(A,ws,"**=",ws,B),
  904	['python']:
  905			(A,python_ws,"**=",python_ws,B)
  906    ]).
  907
  908minus_equals_(Data,[A,B]) -->
  909    langs_to_output(Data,minus_equals,[
  910    ['janus','coffeescript','python','visual basic','visual basic .net','vala','nim','perl 6','dart','perl','typescript','java','c','c++','c#','javascript','php','haxe','hack','julia','scala','rust','go','swift']:
  911			(A,python_ws,"-=",python_ws,B),
  912	['english_temp']:		
  913			(
  914				A,python_ws,"-=",python_ws,B;
  915				"subtract",python_ws_,B,python_ws_,"from",python_ws_,A
  916			),
  917	['haskell','erlang','fortran','ocaml','minizinc','octave','delphi']:
  918			(A,ws,"=",ws,A,ws,"-",ws,B),
  919	['picat']:
  920			(A,ws,":=",ws,A,ws,"-",ws,B),
  921	['rebol']:
  922			(A,ws,":",ws,A,ws,"-",ws,B),
  923	['livecode']:
  924			("subtract",ws_,B,ws_,"from",ws_,A),
  925	['seed7']:
  926			(A,ws,"-:=",ws,B)
  927    ]).
  928    
  929assert_(Data,[A]) -->
  930        langs_to_output(Data,assert,[
  931		['javascript','scala','c','c++','lua','swift','php','ceylon']:
  932                ("assert",ws,"(",ws,A,ws,")"),
  933        ['c#','visual basic .net']:
  934                ("Debug",ws,".",ws,"Assert",ws,"(",ws,A,ws,")"),
  935        ['clojure']:
  936                ("(",ws,"assert",ws_,A,ws,")"),
  937        ['r']:
  938                ("stopifnot",ws,"(",ws,A,ws,")"),
  939		['cython']:
  940				("assert",python_ws_,A),
  941		['java','haskell']:
  942				("assert",ws_,A)
  943		]).
  944
  945
  946print_(Data,[A]) -->        
  947        langs_to_output(Data,print,[
  948        ['java']:
  949			("System",ws,".",ws,"out",ws,".",ws,"print",ws,"(",ws,A,ws,")"),
  950		['c#']:
  951			("Console",ws,".",ws,"Write",ws,"(",ws,A,ws,")"),
  952		['prolog','constraint handling rules']:
  953			("write",ws,"(",ws,A,ws,")"),
  954		['perl']:
  955			("print",ws,"(",ws,A,ws,")"),
  956		['lua']:
  957			("io",ws,".",ws,"write",ws,"(",ws,A,ws,")"),
  958		['php']:
  959			(
  960				"echo",ws_,A;
  961				"echo",ws,"(",ws,A,ws,")"
  962			),
  963		['c++']:
  964			("cout",ws,"<<",ws,A)
  965        ]).
  966
  967%logarithm with e as the base
  968log_base_e_(Data,[A]) -->
  969	langs_to_output(Data,log_base_e,[
  970		['javascript','java','ruby']:
  971			("Math",ws,".",ws,"log",ws,"(",ws,A,ws,")",!),
  972		['c#']:
  973			("Math",ws,".",ws,"Log",ws,"(",ws,A,ws,")",!),
  974		['python','lua']:
  975			("math",python_ws,".",python_ws,"log",python_ws,"(",python_ws,A,python_ws,")",!),
  976		['perl','c','sympy','php']:
  977			("log",ws,"(",ws,A,ws,")"),
  978		['haskell']:
  979			("(",ws,"log",ws_,A,ws,")")
  980	]).
  981
  982%logarithm with N as the base
  983log_base_n_(Data,[A,N]) -->
  984	langs_to_output(Data,log_base_n,[
  985		['c#']:
  986			("Math",ws,".",ws,"Log",ws,"(",ws,A,ws,",",ws,N,ws,")"),
  987		['ruby']:
  988			("Math",ws,".",ws,"log",ws,"(",ws,A,ws,",",ws,N,ws,")")
  989	]).
  990
  991%logarithm with N as the base
  992log_base_10_(Data,[A]) -->
  993	langs_to_output(Data,log_base_n,[
  994		['java']:
  995			("Math",ws,".",ws,"log10",ws,"(",ws,A,ws,")"),
  996		['c#']:
  997			("Math",ws,".",ws,"Log10",ws,"(",ws,A,ws,")")
  998	]).
  999
 1000println_(Data,[A,Type]) -->
 1001		langs_to_output(Data,println,[
 1002		['cython','lua']:
 1003                ("print",python_ws,"(",python_ws,A,python_ws,")"),
 1004        ['python']:
 1005                ("print",python_ws,"(",python_ws,A,python_ws,")";"print",python_ws_,A),
 1006        ['ocaml']:
 1007				(
 1008					"print_int",ws_,A,{Type=int};
 1009					"print_string",ws_,A,{Type=string}
 1010				),
 1011        ['english_temp']:
 1012                (synonym("print"),python_ws,"(",python_ws,A,python_ws,")";synonym("print"),python_ws_,A),
 1013        ['minizinc']:
 1014                ("trace",ws,"(",ws,A,ws,",",ws,"true",ws,")"),
 1015        ['perl 6']:
 1016                ("say",ws_,A),
 1017        ['erlang']:
 1018                ("io",ws,":",ws,"fwrite",ws,"(",ws,A,ws,")"),
 1019        ['c++']:
 1020                ("cout",ws,"<<",ws,A,"<<",ws,"endl"),
 1021        ['haxe']:
 1022                ("trace",ws,"(",ws,A,ws,")"),
 1023        ['go']:
 1024                ("fmt",ws,".",ws,"Println",ws,"(",ws,A,ws,")"),
 1025        ['c#','visual basic .net']:
 1026                ("Console",ws,".",ws,"WriteLine",ws,"(",ws,A,ws,")"),
 1027        ['rebol','fortran','perl','php']:
 1028                ("print",ws_,A),
 1029        ['ruby']:                            
 1030                ("puts",ws,"(",ws,A,ws,")"),
 1031        ['scala','julia','swift','picat']:
 1032                ("println",ws,"(",ws,A,ws,")"),
 1033        ['javascript','typescript']:
 1034                ("console",ws,".",ws,"log",ws,"(",ws,A,ws,")"),
 1035        ['coffeescript']:
 1036                ("console",python_ws,".",python_ws,"log",python_ws,"(",python_ws,A,python_ws,")"),
 1037        ['englishscript','cython','ceylon','r','gosu','dart','vala','perl','php','hack','awk']:
 1038                ("print",python_ws,"(",python_ws,A,python_ws,")"),
 1039        ['java']:
 1040                ("System",ws,".",ws,"out",ws,".",ws,"println",ws,"(",ws,A,ws,")"),
 1041        ['c']:
 1042                ("printf",ws,"(",ws,A,ws,")"),
 1043        ['haskell']:
 1044                ("(",ws,"putStrLn",ws_,A,ws,")"),
 1045        ['hy','common lisp']:
 1046                ("(",ws,"print",ws_,A,ws,")"),
 1047        ['rust']:
 1048                ("println!(",ws,A,ws,")"),
 1049        ['octave']:
 1050                ("disp",ws,"(",ws,A,ws,")"),
 1051        ['chapel','d','seed7','prolog','constraint handling rules']:
 1052                ("writeln",ws,"(",ws,A,ws,")"),
 1053        ['delphi']:
 1054                ("WriteLn",ws,"(",ws,A,ws,")"),
 1055        ['frink']:
 1056                ("print",ws,"[",ws,A,ws,"]"),
 1057        ['wolfram']:
 1058                ("Print",ws,"[",ws,A,ws,"]"),
 1059        ['z3']:
 1060                ("(",ws,"echo",ws_,A,ws,")"),
 1061        ['monkey x']:
 1062                ("Print",ws_,A)
 1063        ]).
 1064
 1065times_equals_(Data,[Name,Expr]) -->
 1066        langs_to_output(Data,times_equals,[
 1067        ['c','c++','java','c#','javascript','php','perl']:
 1068                (Name,ws,"*=",ws,Expr),
 1069        ['coffeescript','python']:
 1070				(Name,python_ws,"*=",python_ws,Expr),
 1071        ['english']:
 1072                (
 1073					Name,ws,"*=",ws,Expr;
 1074					"multiply",python_ws_,Name,python_ws_,"by",python_ws_,Expr
 1075				)
 1076        
 1077        ]).
 1078
 1079append_to_string_(Data,[Name,Expr]) -->
 1080        langs_to_output(Data,append_to_string,[
 1081        [c,'java','c#',javascript]:
 1082                (Name,python_ws,"+=",python_ws,Expr),
 1083        [php,'perl']:
 1084                (Name,ws,".=",ws,Expr)
 1085        ]).
 1086
 1087append_to_array_(Data,[Name,Expr]) -->
 1088        langs_to_output(Data,append_to_array,[
 1089        ['javascript']:
 1090                (Name,ws,".",ws,"push",ws,"(",ws,Expr,ws,")"),
 1091        ['python']:
 1092                (Name,python_ws,".",python_ws,"append",python_ws,"(",python_ws,Expr,python_ws,")"),
 1093        ['php']:
 1094                ("array_push",ws,"(",ws,Expr,ws,")"),
 1095        ['perl']:
 1096                ("push",ws,"(",ws,Expr,ws,")")
 1097        ]).
 1098
 1099throw_(Data,[A]) -->
 1100	langs_to_output(Data,throw,[
 1101	['ocaml']:
 1102			("raise",ws_,A),
 1103	['javascript','dart','java','c++','swift','rebol','haxe','c#','picat','scala']:
 1104			("throw",ws_,A),
 1105	['julia','e']:
 1106			("throw",ws,"(",ws,A,ws,")"),
 1107	['perl','perl 6']:
 1108			("die",ws_,A),
 1109	['octave']:
 1110			("error",ws,"(",ws,A,ws,")"),
 1111	['php']:
 1112			("throw",ws_,"new",ws_,"Exception",ws,"(",ws,A,ws,")"),
 1113	['pseudocode']:
 1114			(statement_with_semicolon(Data,_,throw(A)))
 1115	]).
 1116
 1117
 1118initialize_empty_var_(Data,[Name,Type]) -->
 1119    langs_to_output(Data,initialize_empty_var,[
 1120    ['swift','scala','typescript']:
 1121			("var",ws_,Name,ws,":",ws,Type),
 1122	['java','systemverilog','c#','c++','c','d','janus','fortran','dart']:
 1123			(Type,ws_,Name),
 1124	['prolog','constraint handling rules']:
 1125			(Type,ws,"(",ws,Name,ws,")"),
 1126	['javascript','haxe']:
 1127			("var",ws_,Name),
 1128	['minizinc']:
 1129			(Type,ws,":",ws,Name),
 1130	['pascal']:
 1131			(Name,ws,":",ws,Type),
 1132	['go']:
 1133			("var",ws_,Name,ws_,Type),
 1134	['z3']:
 1135			("(",ws,"declare-const",ws_,Name,ws_,Type,ws,")"),
 1136	['julia']:
 1137			("local",ws_,Name),
 1138	['perl']:
 1139			("my",ws_,Name),
 1140	['perl 6']:
 1141			("my",ws_,Type,ws_,Name),
 1142	['z3py']:
 1143			(Name,ws,"=",ws,Type,ws,"(",ws,"'",ws,Name,ws,"'",ws,")")
 1144	]).
 1145
 1146set_dict_(Data,[Name,Index,Value]) -->
 1147	langs_to_output(Data,set_dict,[
 1148    ['javascript','lua','c++','haxe','c#','ruby']:
 1149			(Name,ws,"[",ws,Index,ws,"]",ws,"=",ws,Value),
 1150	['scala']:
 1151			(
 1152				%this adds to a Map
 1153				(Name,ws,"+",ws,"=",ws,"(",ws,Index,ws,"->",ws,Value,ws,")");
 1154				%this updates a map with the key already present
 1155				(Name,ws,"(",ws,Key,ws,")",ws,"=",ws,Value)
 1156			),
 1157	['python','cython']:
 1158			(Name,python_ws,"[",python_ws,Index,python_ws,"]",python_ws,"=",python_ws,Value),
 1159	['english_temp']:
 1160			(
 1161				(
 1162				optional_the(Index),python_ws_,"of",python_ws_,Name;
 1163				Name,"'s",python_ws_,Index
 1164				),python_ws_,"is",python_ws_,Value;
 1165				Name,python_ws,"[",python_ws,Index,python_ws,"]",python_ws,"=",python_ws,Value
 1166			),
 1167	['gnu smalltalk']:
 1168			(Name,ws_,"at:",ws_,Index,ws_,"put:",ws_,Value),
 1169	['prolog','constraint handling rules']:
 1170			("member",ws,"(",ws,Name,ws,",",ws,Index,ws,"-",ws,Value,ws,")"),
 1171	['java']:	
 1172			(Name,ws,".",ws,"put",ws,"(",ws,Value,ws,")")
 1173	]).
 1174
 1175%from A (inclusive) to B (exclusive)
 1176range_(Data,[A,B]) -->
 1177	langs_to_output(Data,range,[
 1178	['swift','perl','picat','minizinc','chapel']:
 1179		("(",ws,A,ws,"..",ws,B,ws,")"),
 1180	['rust']:
 1181		("(",ws,A,ws,"...",ws,B,ws,")"),
 1182	["python"]:
 1183		("range",python_ws,"(",python_ws,A,python_ws,",",B,python_ws,"-",python_ws,"1",python_ws,")")
 1184    ]).
 1185
 1186get_user_input_(Data) -->
 1187        langs_to_output(Data,get_user_input,[
 1188			['python']:
 1189				("input",python_ws,"(",python_ws,")"),
 1190			['perl']:
 1191				"<>",
 1192			['ruby']:
 1193				"gets",
 1194			['swift']:
 1195				("readLine",ws,"(",ws,")"),
 1196			['php']:
 1197				("readline",ws,"(",ws,")"),
 1198			['OCaml']:
 1199				("read_line",ws,"(",ws,")"),
 1200			['perl 6']:
 1201				("prompt",ws,"(",ws,")"),
 1202			['prolog']:
 1203				("read",ws,"(",ws,Var,ws,")"),
 1204			['julia']:
 1205				("chomp",ws,"(",ws,"readline",ws,"(",ws,")",ws,")"),
 1206			['lua']:
 1207				("io",ws,".",ws,"stdin:read",ws,"(",ws,")"),
 1208			['c#']:
 1209				("Console",ws,".",ws,"ReadLine",ws,"(",ws,")")
 1210        ]).
 1211
 1212get_user_input_with_prompt_(Data,[Var,Prompt]) -->
 1213        langs_to_output(Data,get_user_input_with_prompt,[
 1214			['python']:
 1215				(Var,python_ws,"=",python_ws,"input",python_ws,"(",python_ws,Prompt,python_ws,")"),
 1216			['php']:
 1217				(Var,ws,"=",ws,"readline",ws,"(",ws,Prompt,ws,")"),
 1218			['perl']:
 1219				("print",ws,"(",ws,Prompt,ws,")",ws,";",ws,"=",ws,"<>"),
 1220			['erlang']:
 1221				(Var,ws,"=",ws,"io:get_line(",ws,Prompt,ws,")")
 1222        ]).
 1223
 1224initializer_list_(Data,[A,Type]) -->
 1225        langs_to_output(Data,initializer_list,[
 1226        %initializer lists in Java should be ArrayLists
 1227        ['lua','pseudocode','picat','c#','c++','c','visual basic','visual basic .net','wolfram']:
 1228                ("{",ws,A,ws,"}"),
 1229        ['java']:
 1230                ("new",ws_,Type,"[]",ws,"{",ws,A,ws,"}"),
 1231		['ocaml']:
 1232				(
 1233					%this is for lists
 1234					"[|",ws,A,ws,"|]";
 1235					%this is for arrays
 1236					"[",ws,A,ws,"]"
 1237				),
 1238		['english']:
 1239                ("{",ws,A,ws,"}";"[",ws,A,ws,"]"),
 1240        ['go']:
 1241				("[]",Type,"{",ws,A,ws,"}"),
 1242        [ 'ruby', 'cosmos', 'python', 'cython', 'nim','d','frink','rebol','octave','julia','prolog','constraint handling rules','minizinc','engscript','cython','groovy','dart','typescript','coffeescript','nemerle','javascript','haxe','haskell','rebol','polish notation','swift']:
 1243                ("[",python_ws,A,python_ws,"]"),
 1244        ['php']:
 1245                ("array",ws,"(",ws,A,ws,")"),
 1246        ['scala']:
 1247                ("Array",ws,"(",ws,A,ws,")"),
 1248        ['perl','chapel']:
 1249                ("(",ws,A,ws,")"),
 1250        ['fortran']:
 1251                ("(/",ws,A,ws,"/)"),
 1252        ['r']:
 1253				("s(",ws,A,ws,")")
 1254        ]).
 1255
 1256%https://rosettacode.org/wiki/Associative_array
 1257
 1258dict_(Data,[A,Type]) -->
 1259		langs_to_output(Data,dict,[
 1260		['python', 'english_temp', 'cosmos', 'ruby', 'lua', 'dart','javascript','typescript','julia','c++','engscript']:
 1261                ("{",python_ws,A,python_ws,"}"),
 1262        ['c#']:
 1263				("new",ws_,"Dictionary<string",ws,",",ws,Type,ws,">{",ws,A,ws,"}"),
 1264        ['java']:
 1265				("new",ws_,"ArrayList<",Type,">().",ws,A),
 1266        ['picat']:
 1267                ("new_map",ws,"(",ws,"[",ws,A,ws,"]",ws,")"),
 1268        ['go']:
 1269                ("map",ws,"[",ws,"Input",ws,"]",ws,"Output",ws,"{",ws,A,ws,"}"),
 1270        ['perl']:
 1271                ("(",ws,A,ws,")"),
 1272        ['php']:
 1273                ("array",ws,"(",ws,A,ws,")"),
 1274        ['haxe','frink','swift','elixir','d','wolfram','prolog','constraint handling rules']:
 1275                ("[",ws,A,ws,"]"),
 1276        ['scala']:
 1277                ("Map",ws,"(",ws,A,ws,")"),
 1278        ['gnu smalltalk']:
 1279                ("Dictionary",ws,"(",ws,A,ws,")"),
 1280        ['octave']:
 1281                ("struct",ws,"(",ws,A,ws,")"),
 1282        ['rebol']:
 1283                ("to-hash",ws,"[",ws,A,ws,"]")
 1284        ]).
 1285
 1286struct_(Data,[Name,Values,Indent]) -->
 1287        langs_to_output(Data,struct,[
 1288			['c']:
 1289				("struct",ws_,Name,ws,"{",ws,Values,(Indent;ws),"}",ws,";"),
 1290			['go']:
 1291				("type",ws_,Name,ws_,"struct",ws,"{",ws,Values,(Indent;ws),"}"),
 1292			['c#']:
 1293				("public",ws,"struct",ws_,Name,ws,"{",ws,Values,(Indent;ws),"}")
 1294        ]).	
 1295
 1296tan_(Data,[Var1]) -->  
 1297        langs_to_output(Data,tan,[
 1298        ['java','ruby','javascript','typescript','haxe']:
 1299                ("Math",ws,".",ws,"tan",ws,"(",ws,Var1,ws,")"),
 1300        ['python','lua']:
 1301                ("math",python_ws,".",python_ws,"tan",python_ws,"(",python_ws,Var1,python_ws,")"),
 1302        ['c','seed7','erlang','picat','mathematical notation','julia','d','php','perl','perl 6','maxima','fortran','minizinc','swift','prolog','octave','dart','haskell','c++','scala']:
 1303                ("tan",ws,"(",ws,Var1,ws,")"),
 1304        ['c#']:
 1305                ("Math",ws,".",ws,"Tan",ws,"(",ws,Var1,ws,")"),
 1306        ['wolfram']:
 1307                ("Tan",ws,"[",ws,Var1,ws,"]"),
 1308        ['rebol']:
 1309                ("tangent/radians",ws_,Var1),
 1310        ['go']:
 1311                ("math",ws,".",ws,"Tan",ws,"(",ws,Var1,ws,")"),
 1312        ['common lisp','racket']:
 1313                ("(",ws,"tan",ws_,"a",ws,")"),
 1314        ['clojure']:
 1315                ("(",ws,"Math/tan",ws_,"a",ws,")")
 1316        ]).
 1317false_(Data) -->
 1318    langs_to_output(Data,'false',[
 1319    ['java','ruby','lua','constraint handling rules','livecode','gap','dafny','z3','perl 6','chapel','c','frink','elixir','pascal','rust','minizinc','engscript','picat','clojure','nim','groovy','d','ceylon','typescript','coffeescript','octave','prolog','julia','vala','f#','swift','c++','nemerle','dart','javascript','erlang','c#','haxe','go','ocaml','scala','php','rebol','hack']:
 1320			("false"),
 1321	['python','pydatalog','hy','cython','autoit','haskell','vbscript','visual basic','monkey x','wolfram','delphi']:
 1322			("False"),
 1323	['perl','awk','tcl']:
 1324			("0"),
 1325	['common lisp']:
 1326			("nil"),
 1327	['racket']:
 1328			("#f"),
 1329	['fortran']:
 1330			(".FALSE."),
 1331	['seed7','r']:
 1332			("FALSE")
 1333    ]).
 1334
 1335true_(Data) --> 
 1336	langs_to_output(Data,'true',[
 1337	['java','ruby','lua','constraint handling rules','livecode','gap','dafny','z3','perl 6','chapel','c','frink','elixir','pseudocode','pascal','minizinc','engscript','picat','rust','clojure','nim','hack','ceylon','d','groovy','coffeescript','typescript','octave','prolog','julia','f#','swift','nemerle','vala','c++','dart','javascript','erlang','c#','haxe','go','ocaml','scala','php','rebol']:
 1338			("true"),
 1339	['python','pydatalog','hy','cython','autoit','haskell','vbscript','visual basic','monkey x','wolfram','delphi']:
 1340			("True"),
 1341	['perl','awk','tcl']:
 1342			("1"),
 1343	['racket']:
 1344			("#t"),
 1345	['common lisp']:
 1346			("t"),
 1347	['fortran']:
 1348			(".TRUE."),
 1349	['r','seed7']:
 1350			("TRUE")
 1351    ]).
 1352
 1353acos_(Data,[Var1]) -->
 1354        langs_to_output(Data,acos,[
 1355        ['c','perl','prolog']:
 1356                ("acos",ws,"(",ws,Var1,ws,")"),
 1357        ['go']:
 1358                ("Acos",ws,"(",ws,Var1,ws,")")
 1359        ]).
 1360
 1361asin_(Data,[Var1]) -->
 1362        langs_to_output(Data,asin,[
 1363        ['c','perl','prolog']:
 1364                ("asin",ws,"(",ws,Var1,ws,")"),
 1365        ['go']:
 1366                ("Asin",ws,"(",ws,Var1,ws,")")
 1367        ]).
 1368
 1369atan_(Data,[Var1]) -->
 1370        langs_to_output(Data,atan,[
 1371        ['c','perl','prolog']:
 1372                ("atan",ws,"(",ws,Var1,ws,")"),
 1373        ['go']:
 1374                ("Atan",ws,"(",ws,Var1,ws,")")
 1375        ]).
 1376
 1377sinh_(Data,[Var1]) -->
 1378	langs_to_output(Data,sinh,[
 1379	['c']:
 1380			("sinh",ws,"(",ws,Var1,ws,")"),
 1381	['c#']:
 1382			("Math",ws,".",ws,"Sinh",ws,"(",ws,Var1,ws,")")
 1383	]).
 1384cosh_(Data,[Var1]) -->
 1385	langs_to_output(Data,cosh,[
 1386	['c']:
 1387			("cosh",ws,"(",ws,Var1,ws,")"),
 1388	['go']:
 1389			("Cosh",ws,"(",ws,Var1,ws,")"),
 1390	['c#']:
 1391			("Math",ws,".",ws,"Cosh",ws,"(",ws,Var1,ws,")")
 1392	]).
 1393
 1394% see http://rosettacode.org/wiki/Real_constants_and_functions#Haskell
 1395abs_(Data,[Var1]) -->
 1396	langs_to_output(Data,abs,[
 1397	['java','javascript']:
 1398			("Math",ws,".",ws,"abs",ws,"(",ws,Var1,ws,")"),
 1399	['ruby']:
 1400			(Var1,ws,".",ws,"abs"),
 1401	['f#','c#']:
 1402			("Math",ws,".",ws,"Abs",ws,"(",ws,Var1,ws,")"),
 1403	['lua']:
 1404			("math",ws,".",ws,"abs",ws,"(",ws,Var1,ws,")"),
 1405	['c','perl','php','python','erlang','prolog']:
 1406			("abs",python_ws,"(",python_ws,Var1,python_ws,")"),
 1407	['wolfram']:
 1408            ("Abs",ws,"[",ws,Var1,ws,"]")
 1409	]).
 1410
 1411sin_(Data,[Var1]) -->
 1412        langs_to_output(Data,sin,[
 1413        ['java','ruby','javascript','typescript','haxe']:
 1414                ("Math",ws,".",ws,"sin",ws,"(",ws,Var1,ws,")"),
 1415        ['python','cython','lua']:
 1416                ("math",python_ws,".",python_ws,"sin",python_ws,"(",python_ws,Var1,python_ws,")"),
 1417        ['c','seed7','erlang','picat','mathematical notation','julia','d','php','perl','perl 6','maxima','fortran','minizinc','swift','prolog','octave','dart','haskell','c++','scala']:
 1418                ("sin",ws,"(",ws,Var1,ws,")"),
 1419        ['c#']:
 1420                ("Math",ws,".",ws,"Sin",ws,"(",ws,Var1,ws,")"),
 1421        ['wolfram']:
 1422                ("Sin",ws,"[",ws,Var1,ws,"]"),
 1423        ['rebol']:
 1424                ("sine/radians",ws_,Var1),
 1425        ['go']:
 1426                ("math",ws,".",ws,"Sin",ws,"(",ws,Var1,ws,")"),
 1427        ['common lisp','racket']:
 1428                ("(",ws,"sin",ws_,Var1,ws,")"),
 1429        ['clojure']:
 1430                ("(",ws,"Math/sin",ws_,Var1,ws,")")
 1431        ]).
 1432
 1433cos_(Data,[Var1]) -->
 1434        langs_to_output(Data,cos,[
 1435        ['java','ruby','javascript','typescript','haxe']:
 1436                ("Math",ws,".",ws,"cos",ws,"(",ws,Var1,ws,")"),
 1437        ['c','seed7','erlang','picat','mathematical notation','julia','d','php','perl','perl 6','maxima','fortran','minizinc','swift','prolog','octave','dart','haskell','c++','scala']:
 1438                ("cos",ws,"(",ws,Var1,ws,")"),
 1439        ['c#']:
 1440                ("Math",ws,".",ws,"Cos",ws,"(",ws,Var1,ws,")"),
 1441        ['wolfram']:
 1442                ("Cos",ws,"[",ws,Var1,ws,"]"),
 1443        ['go']:
 1444                ("math",ws,".",ws,"Cos",ws,"(",ws,Var1,ws,")"),
 1445        ['python','lua']:
 1446                ("math",python_ws,".",python_ws,"cos",python_ws,"(",python_ws,Var1,python_ws,")"),
 1447        ['rebol']:
 1448                ("cosine/radians",ws_,Var1),
 1449        ['common lisp','racket']:
 1450                ("(",ws,"cos",ws_,Var1,ws,")"),
 1451        ['clojure']:
 1452                ("(",ws,"Math/cos",ws_,Var1,ws,")")
 1453        ]).
 1454
 1455% see https://rosettacode.org/wiki/Real_constants_and_functions
 1456ceiling_(Data,[Params]) -->
 1457        langs_to_output(Data,ceiling,[
 1458                ['javascript','java']:
 1459					("Math",ws,".",ws,"ceil",ws,"(",ws,Params,ws,")"),
 1460				['c#']:
 1461					("Math",ws,".",ws,"Ceiling",ws,"(",ws,Params,ws,")"),
 1462				['python','lua']:
 1463					("math",python_ws,".",python_ws,"ceil",python_ws,"(",python_ws,Params,python_ws,")"),
 1464				['c','perl','php','pl/i','octave']:
 1465					("ceil",ws,"(",ws,Params,ws,")"),
 1466				['perl 6','prolog']:
 1467					("ceiling",ws,"(",ws,Params,ws,")"),
 1468				['wolfram']:
 1469					("Ceiling",ws,"[",ws,Params,ws,"]")
 1470        ]).
 1471        
 1472% see https://rosettacode.org/wiki/Real_constants_and_functions
 1473floor_(Data,[Params]) -->
 1474        langs_to_output(Data,floor,[
 1475                ['javascript','java','actionscript']:
 1476                        ("Math",ws,".",ws,"floor",ws,"(",ws,Params,ws,")"),
 1477                ['c#']:
 1478                        ("Math",ws,".",ws,"Floor",ws,"(",ws,Params,ws,")"),
 1479                ['python','lua']:
 1480                        ("math",python_ws,".",python_ws,"floor",python_ws,"(",python_ws,Params,python_ws,")"),
 1481                ['c','perl','php','pl/i','octave','prolog']:
 1482						("floor",ws,"(",ws,Params,ws,")")
 1483        ]).
 1484
 1485copy_array_(A1,A2) -->
 1486	langs_to_output(Data,copy_array,[
 1487		['python']:
 1488			(A2,"=","list",ws,"(",ws,A1)
 1489	]).
 1490	
 1491anonymous_function_(Data,[Type,Params,B]) -->
 1492		langs_to_output(Data,anonymous_function,[
 1493		['matlab','octave']:
 1494                ("(",ws,"@",ws,"(",ws,Params,ws,")",ws,B,ws,")"),
 1495        ['picat']:
 1496                ("lambda",ws,"(",ws,"[",ws,Params,ws,"]",ws,",",ws,B,ws,")"),
 1497        ['javascript','typescript','haxe','r','php']:
 1498                (
 1499					"function",ws,"(",ws,Params,ws,")",ws,"{",ws,B,ws,"}";
 1500					%arrow functions
 1501					"(",ws,Params,ws,")",ws,"=>",ws,"{",ws,B,ws,"}"
 1502				),
 1503        ['haskell']:
 1504                ("(",ws,"\\",ws,Params,ws,"->",ws,B,ws,")"),
 1505        ['frink']:
 1506                ("{",ws,"|",ws,Params,ws,"|",ws,B,ws,"}"),
 1507        ['erlang']:
 1508                ("fun",ws,"(",ws,Params,ws,")",ws_,B,"end"),
 1509        ['julia','lua']:
 1510                ("function",ws,"(",ws,Params,ws,")",ws_,B,"end"),
 1511        ['swift']:
 1512                ("{",ws,"(",ws,Params,ws,")",ws,"->",ws,Type,ws_,"in",ws_,B,ws,"}"),
 1513        ['go']:
 1514                ("func",ws,"(",ws,Params,ws,")",ws,Type,ws,"{",ws,B,ws,"}"),
 1515        ['dart','scala']:
 1516                ("(",ws,"(",ws,Params,ws,")",ws,"=>",ws,B,ws,")"),
 1517        ['c++']:
 1518                ("[",ws,"=",ws,"]",ws,"(",ws,Params,ws,")",ws,"->",ws,Type,ws,"{",ws,B,ws,"}"),
 1519        ['java']:
 1520                ("(",ws,Params,ws,")",ws,"->",ws,"{",ws,B,ws,"}"),
 1521        ['haxe']:
 1522                ("(",ws,"name",ws_,Params,ws,"->",ws,B,ws,")"),
 1523        ['delphi']:
 1524                ("function",ws,"(",ws,Params,ws,")",ws,"begin",ws_,B,"end",ws,"),"),
 1525        ['d']:
 1526                ("(",ws,Params,ws,")",ws,"{",ws,B,ws,"}"),
 1527        ['rebol']:
 1528                ("func",ws_,"[",ws,Params,ws,"]",ws,"[",ws,B,ws,"]"),
 1529        ['rust']:
 1530                ("fn",ws,"(",ws,Params,ws,")",ws,"{",ws,B,ws,"}")
 1531        ]).
 1532
 1533type_conversion_(['perl'|_],[Type1,Type2,Arg]) -->
 1534	{member(Type1,[int,string,bool,double]),member(Type2,[int,string,bool,double])},
 1535	Arg.
 1536
 1537type_conversion_(Data,[_,Type2,Arg]) -->
 1538	{Data=['python'|_]},
 1539	(type(Data,Type2),python_ws,"(",python_ws,Arg,python_ws,")").
 1540
 1541type_conversion_(Data,[_,Type2,Arg]) -->
 1542	{Data=['php'|_]},
 1543	("(",ws,type(Data,Type2),ws,")",ws,"(",ws,Arg,ws,")").
 1544
 1545type_conversion_(Data,[string,[array,char],Arg]) -->
 1546	langs_to_output(Data,[type_conversion,string,[array,char]],[
 1547        ['python','cython']:
 1548			("list",python_ws,"(",python_ws,Arg,python_ws,")"),
 1549		['php']:
 1550			("str_split",ws,"(",ws,Arg,ws,")"),
 1551		['swift']:
 1552			("Array",ws,"(",ws,Arg,ws,")"),
 1553		['javascript']:
 1554			("Array",ws,".",ws,"from",ws,"(",ws,Arg,ws,")"),
 1555		['java']:
 1556			(Arg,ws,".",ws,"toCharArray",ws,"(",ws,")"),
 1557		['c#','visual basic .net']:
 1558			(Arg,ws,".",ws,"ToCharArray",ws,"(",ws,")"),
 1559		['ruby']:
 1560			(Arg,ws,".",ws,"char"),
 1561		['perl']:
 1562			("(",ws,split,ws_,"//",ws_,Arr,ws,")"),
 1563		['haskell']:
 1564			(Arg)
 1565	]).
 1566
 1567type_conversion_(Data,[char,string,Arg]) -->
 1568	langs_to_output(Data,[type_conversion,char,string],[
 1569		['java']:
 1570			("String",ws,".",ws,"valueOf",ws,"(",ws,Arg,ws,")"),
 1571		['c#']:
 1572			(
 1573				Arg,ws,".",ws,"ToString",ws,"(",ws,")";
 1574				"Char",ws,".",ws,"ToString(",ws,Arg,ws,")"
 1575			)
 1576	]).
 1577
 1578type_conversion_(Data,[int,string,Arg]) -->
 1579		langs_to_output(Data,[type_conversion,int,string],[
 1580        ['erlang']:
 1581			("integer_to_list",ws,"(",ws,Arg,ws,")"),
 1582        ['c#']:
 1583                (Arg,ws,".",ws,"ToString",ws,"(",ws,")"),
 1584        ['ruby']:
 1585                (Arg,ws,".",ws,"to_s"),
 1586        ['java']:
 1587				("Integer",ws,".",ws,"toString",ws,"(",ws,Arg,ws,")";
 1588				"String",ws,".",ws,"valueOf",ws,"(",ws,Arg,ws,")"),
 1589        ['javascript','swift']:
 1590                ("String",ws,"(",ws,Arg,ws,")"),
 1591        ['c++']:
 1592				("std::to_string",ws,"(",ws,Arg,ws,")"),
 1593		['haskell']:
 1594				("(",ws,"show",ws_,Arg,")"),
 1595		['ocaml']:
 1596				("(",ws,"string_of_int",ws_,Arg,")"),
 1597		['python']:
 1598				("str",python_ws,"(",python_ws,Arg,python_ws,")")
 1599        ]).
 1600
 1601type_conversion_(['c#'|_],[_,bool,Arg]) -->
 1602	("Convert",ws,".",ws,"toBoolean",ws,"(",ws,Arg,ws,")").
 1603
 1604type_conversion_(['c#'|_],[_,int,Arg]) -->
 1605	("Convert",ws,".",ws,"toInt32",ws,"(",ws,Arg,ws,")").
 1606
 1607type_conversion_(['c#'|_],[_,double,Arg]) -->
 1608	("Convert",ws,".",ws,"toDouble",ws,"(",ws,Arg,ws,")").
 1609
 1610type_conversion_(Data,[bool,string,Arg]) -->
 1611		langs_to_output(Data,[type_conversion,bool,string],[
 1612        ['python']:
 1613				("str",python_ws,"(",python_ws,Arg,python_ws,")"),
 1614        ['java']:
 1615				("Boolean",ws,".",ws,"toString",ws,"(",ws,Arg,ws,")";
 1616				"String",ws,".",ws,"valueOf",ws,"(",ws,Arg,ws,")"),
 1617		['php']:
 1618			("var_export",ws,"(",ws,Arg,ws,",",ws,"true",ws,")")
 1619        ]).
 1620
 1621type_conversion_(Data,[string,bool,Arg]) -->
 1622		langs_to_output(Data,[type_conversion,string,bool],[
 1623        ['python']:
 1624				("boolean",python_ws,"(",python_ws,Arg,python_ws,")"),
 1625        ['java']:
 1626				("Boolean",ws,".",ws,"parseBoolean",ws,"(",ws,Arg,ws,")";
 1627				"Boolean",ws,".",ws,"valueOf",ws,"(",ws,Arg,ws,")")
 1628        ]).
 1629
 1630type_conversion_(Data,[string,int,Arg]) -->
 1631		langs_to_output(Data,[type_conversion,string,int],[
 1632        ['erlang']:
 1633			("list_to_integer",ws,"(",ws,Arg,ws,")"),
 1634        ['javascript']:
 1635			("parseInt",ws,"(",ws,Arg,ws,")"),
 1636		['ocaml']:
 1637				("(",ws,"int_of_string",ws_,Arg,")"),
 1638		['coffeescript']:
 1639			("parseInt",python_ws,"(",python_ws,Arg,python_ws,")"),
 1640		['c']:
 1641			(
 1642				"(",ws,"int",ws,")",ws_,"strtol",ws,"(",ws,Arg,ws,",",ws,"(",ws,"char",ws_,"**",ws,")",ws,"NULL,",ws,"10",ws,")";
 1643				"atoi",ws,"(",ws,Arg,ws,")"
 1644			),
 1645		['ruby']:
 1646			(ws,Arg,".",ws,"to_i"),
 1647        ['java']:
 1648			("Integer",ws,".",ws,"parseInt",ws,"(",ws,Arg,ws,")"),
 1649		['haxe']:
 1650			("Std",ws,".",ws,"parseInt",ws,"(",ws,Arg,ws,")"),
 1651		['c#']:
 1652			("Int32",ws,".",ws,"Parse",ws,"(",ws,Arg,ws,")"),
 1653		['swift']:
 1654			("Int",ws,"(",ws,Arg,ws,")"),
 1655		['c++']:
 1656			("atoi",ws,"(",Arg,".",ws,"c_str",ws,"(",ws,")",ws,")"),
 1657		['haskell']:
 1658			("(",ws,"read",ws_,Arg,")"),
 1659		['python']:
 1660			("int",python_ws,"(",python_ws,Arg,python_ws,")"),
 1661		['lua']:
 1662			("tonumber",python_ws,"(",python_ws,Arg,python_ws,")")
 1663        ]).
 1664
 1665type_conversion_(Data,[string,double,Arg]) -->
 1666		langs_to_output(Data,[type_conversion,string,double],[
 1667        ['python']:
 1668			("float",python_ws,"(",python_ws,Arg,python_ws,")"),
 1669		['c']:
 1670			(
 1671				"strtod",ws,"(",ws,Arg,ws,")";
 1672				"atof",ws,"(",ws,Arg,ws,")"
 1673			),
 1674        ['java']:
 1675			("Double",ws,".",ws,"parseDouble",ws,"(",ws,Arg,ws,")"),
 1676		['haxe']:
 1677			("Double",ws,".",ws,"parseFloat",ws,"(",ws,Arg,ws,")"),
 1678		['lua']:
 1679			("tonumber",ws,"(",ws,Arg,ws,")"),
 1680		['javascript']:
 1681			("Number",ws,"(",ws,Arg,ws,")"),
 1682		['coffeescript']:
 1683			("Number",python_ws,"(",python_ws,Arg,python_ws,")"),
 1684		['ruby']:
 1685			(Arg,ws,".",ws,"to_f"),
 1686		['perl']:
 1687			Arg,
 1688		['c++']:
 1689			("std::stod",ws,"(",ws,Arg,ws,")")
 1690        ]).
 1691
 1692type_conversion_(Data,[double,string,Arg]) -->
 1693		langs_to_output(Data,[type_conversion,double,string],[
 1694        ['python']:
 1695			("str",python_ws,"(",python_ws,Arg,python_ws,")"),
 1696		['haskell']:
 1697			("(",python_ws,"show",python_ws_,Arg,python_ws,")"),
 1698		['java']:
 1699			("String",ws,".",ws,"valueOf",ws,"(",ws,Arg,ws,")";
 1700			"Double",ws,".",ws,"toString",ws,"(",Arg,")"),
 1701		['c++']:
 1702			("std::to_string",ws,"(",ws,Arg,ws,")"),
 1703		['perl']:
 1704			Arg,
 1705		['swift']:
 1706			("String",ws,"(",ws,Arg,ws,")"),
 1707		['javascript']:
 1708			("toString",ws,"(",ws,Arg,ws,")"),
 1709		['coffeescript']:
 1710			("toString",python_ws,"(",python_ws,Arg,python_ws,")")
 1711        ]).
 1712
 1713static_method_call_(Data,[Class_name,Function_name,Args]) -->
 1714    langs_to_output(Data,static_method_call,[
 1715    ['java','javascript','c#']:
 1716		(Class_name,".",Function_name,ws,"(",ws,Args,ws,")"),
 1717	['python','coffeescript']:
 1718		(Class_name,".",Function_name,ws,"(",python_ws,Args,python_ws,")"),
 1719	['php','c++']:
 1720		(Class_name,"::",Function_name,ws,"(",ws,Args,ws,")"),
 1721	['perl']:
 1722		(Class_name,"->",Function_name,ws,"(",ws,Args,ws,")")
 1723    ]).
 1724instance_method_call_(Data,[Instance_name,Function_name,Args]) -->
 1725	langs_to_output(Data,instance_method_call,[
 1726    ['java','haxe','javascript','c#','c++']:
 1727		(Instance_name,".",Function_name,ws,"(",ws,Args,ws,")"),
 1728	['logtalk']:
 1729		(Instance_name,"::",Function_name,ws,"(",ws,Args,ws,")"),
 1730	['perl']:
 1731		(Instance_name,"->",Function_name,ws,"(",ws,Args,ws,")")
 1732    ]).
 1733
 1734plus_plus_(Data,[Name]) -->
 1735        langs_to_output(Data,plus_plus,[
 1736        ['javascript','java','c','php']:
 1737			(Name,ws,"++"),
 1738		['ruby']:
 1739			(Name,ws,"=",ws,Name,ws,"+",ws,"1")
 1740        ]).
 1741
 1742set_array_index_(Data,[Name,Index,Value]) -->
 1743	set_var_(Data,[access_array_(Data,[Name,Index]),Value]).
 1744
 1745mod_(Data,[A,B]) -->
 1746    langs_to_output(Data,mod,[
 1747    ['java','lua','ruby','perl 6','python','cython','rust','typescript','frink','ooc','genie','pike','ceylon','pawn','powershell','coffeescript','gosu','groovy','engscript','awk','julia','scala','f#','swift','r','perl','nemerle','haxe','php','hack','vala','tcl','go','dart','javascript','c','c++','c#']:
 1748        (A,python_ws,"%",python_ws,B),
 1749    ['rebol']:
 1750        ("mod",ws_,A,ws_,B),
 1751    ['haskell','seed7','minizinc','ocaml','delphi','pascal','picat','livecode']:
 1752        (A,ws_,"mod",ws_,B),
 1753    ['prolog','octave','matlab','autohotkey','fortran']:
 1754        ("mod",ws,"(",ws,A,ws,",",ws,B,ws,")"),
 1755    ['erlang']:
 1756        (A,ws_,"rem",ws_,B),
 1757    ['clips','clojure','common lisp','z3']:
 1758        ("(",ws,"mod",ws_,A,ws_,B,ws,")"),
 1759    ['visual basic','monkey x']:
 1760        (A,ws_,"Mod",ws_,B),
 1761    ['wolfram']:
 1762        ("Mod",ws,"[",ws,A,ws,",",ws,B,ws,"]")
 1763    ]).
 1764
 1765synonym("greater") --> "more".
 1766synonym("each") --> "every";"all".
 1767synonym("print") --> "write".
 1768synonym("=") --> "equals";"is".
 1769
 1770synonym("+") --> python_ws_,"plus",python_ws_.
 1771synonym("and") --> "and";"but";"although".
 1772synonym("-") --> python_ws_,"minus",python_ws_.
 1773synonym("*") -->
 1774	python_ws_,"times",python_ws_;
 1775	python_ws_,"multiplied",python_ws_,"by",python_ws_.
 1776synonym("/") -->
 1777	python_ws_,"divided",python_ws_,"by",python_ws_.
 1778synonym(A) --> A.
 1779synonym("does not equal") -->
 1780	"does",ws_,"not",ws_,"equal";"is",ws_,"not";"cannot",ws_,"be";"!=";"!==".
 1781
 1782arithmetic_(Data,[Exp1,Exp2,Symbol]) -->
 1783        {prefix_arithmetic_langs(Prefix_arithmetic_langs)},
 1784        langs_to_output(Data,arithmetic,[
 1785		['english']:
 1786		(
 1787			Exp1,ws,synonym(Symbol),ws,Exp2;
 1788			"the",ws_,"sum",ws_,"of",ws_,Exp1,ws_,"and",ws_,Exp2,{Symbol="+"};
 1789			"the",ws_,"product",ws_,"of",ws_,Exp1,ws_,"and",ws_,Exp2,{Symbol="*"}
 1790		),
 1791		Infix_arithmetic_langs:
 1792                (Exp1,ws,Symbol,ws,Exp2),
 1793		Prefix_arithmetic_langs:
 1794                ("(",ws,Symbol,ws_,Exp1,ws_,Exp2,ws,")")
 1795        ]).
 1796
 1797string_matches_string_(Data,[Str,Reg]) -->
 1798        langs_to_output(Data,string_matches_string,[
 1799        ['java']:
 1800            (Str,ws,".",ws,"matches",ws,"(",ws,Reg,ws,")"),
 1801        ['php']:
 1802            ("preg_match",ws,"(",ws,Reg,ws,",",ws,Str,ws,")")
 1803        ]).
 1804
 1805new_regex_(Data,[A]) -->
 1806        langs_to_output(Data,new_regex,[
 1807        ['scala','c#']:
 1808            ("new",ws,"Regex",ws,"(",ws,A,ws,")"),
 1809        ['javascript']:
 1810            ("new",ws,"RegExp",ws,"(",ws,A,ws,")"),
 1811        ['c++']:
 1812            ("regex",ws,"::",ws,"regex",ws,"(",ws,A,ws,")")
 1813        ]).
 1814
 1815foreach_with_index_(Data,[Array,Var,Index,Type,Body,Indent]) -->
 1816        langs_to_output(Data,foreach_with_index,[
 1817			['lua']:
 1818				("for",ws_,Index,ws,",",ws,Var,ws_,"in",ws_,"pairs",ws,"(",ws,Array,ws,")",ws_,"do",ws_,Body,(Indent;ws_),"end"),
 1819			['python']:
 1820				("for",python_ws_,Index,python_ws,",",python_ws,Var,python_ws_,"in",python_ws_,"enumerate",python_ws,"(",python_ws,Array,python_ws,"):",python_ws,Body),
 1821			['english_temp']:
 1822				(("for";"for",python_ws,synonym("each")),python_ws_,Index,python_ws,",",python_ws,Var,python_ws_,"in",python_ws_,"enumerate",python_ws,"(",python_ws,Array,python_ws,"):",python_ws,Body),
 1823			['php']:
 1824				("foreach",ws,"(",ws,Array,ws_,"as",ws_,Index,ws,"=>",ws,Var,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1825			['javascript','typescript']:
 1826				(Array,ws,".",ws,"forEach",ws,"(",ws,"function",ws,"(",ws,Var,ws,",",ws,Index,ws,")",ws,"{",ws,Body,(Indent;ws),"}",ws,")",ws,";"),
 1827			['ruby']:
 1828				(Array,ws,".",ws,"each_with_index",ws_,"do",ws,"|",ws,Var,ws,",",ws,Index,ws,"|",ws,Body,(Indent;ws_),"end"),
 1829			['swift']:
 1830				("for",ws,"(",ws,Index,ws,",",ws,Var,ws,")",ws_,"in",ws_,Array,ws,".",ws,"enumerated",ws,"(",ws,")",ws,"{",ws,Body,(Indent;ws),"}")
 1831		]).
 1832
 1833foreach_(Data,[Array,Var,Type,Body,Indent]) -->
 1834        langs_to_output(Data,foreach,[
 1835        ['perl']:
 1836                ("for",ws_,Var,ws_,"(",ws,Array,ws,")",ws,"{",!,ws,Body,(Indent;ws),"}"),
 1837        ['ruby']:
 1838				(Array,ws,".",ws,"each",ws_,"do",ws,"|",ws,Var,ws,"|",ws,Body,(Indent;ws_),"end"),
 1839        ['erlang']:
 1840				("foreach",ws,"(",ws,"fun",ws,"(",ws,Var,ws,")",ws,"->",ws,Body,ws_,"end",ws,",",ws,Array,ws,")"),
 1841		['c']:
 1842			({unique_var(X)},Type,ws_,Var,ws,";",ws_,"int",ws_,X,ws,";",ws,"for",ws,"(",ws,"int",ws_,X,ws,"=",ws,"0",ws,";",ws,X,ws,"<",ws,array_length(Data,[Array]),ws,";",ws,X,ws,"++",ws,")",ws,"{",ws,Var,ws,"=",ws,Array,ws,"[",ws,X,ws,"]",ws,";",ws,Body,(Indent;ws),"}"),
 1843        ['lua']:
 1844				("for",ws_,"_",ws,",",ws,Var,ws_,"in",ws_,"pairs",ws,"(",ws,Array,ws,")",ws_,"do",ws_,Body,(Indent;ws_),"end"),
 1845        ['seed7']:
 1846                ("for",ws_,Var,ws_,"range",ws_,Array,ws_,"do",ws_,Body,(Indent;ws_),"end",ws_,"for;"),
 1847        ['javascript','typescript']:
 1848                (Array,ws,".",ws,"forEach",ws,"(",ws,"function",ws,"(",ws,Var,ws,")",ws,"{",!,ws,Body,(Indent;ws),"}",ws,")",ws,";"),
 1849        ['octave']:
 1850                ("for",ws_,Var,ws,"=",ws,Array,ws_,Body,(Indent;ws_),"endfor"),
 1851        ['prolog']:
 1852				("foreach",ws,"(",ws,"member",ws,"(",Var,ws,",",ws,Array,")",ws,",",ws,"(",ws,Body,ws,")",ws,")"),
 1853        ['z3']:
 1854                ("(",ws,"forall",ws_,"(",ws,"(",ws,Var,ws_,"a",ws,")",ws,")",ws_,"(",ws,"=>",ws,"select",ws_,Array,ws,")",ws,")"),
 1855        ['gap']:
 1856                ("for",ws_,Var,ws_,"in",ws_,Array,ws_,"do",ws_,Body,ws_,"od;"),
 1857        ['minizinc']:
 1858                ("forall",ws,"(",ws,Var,ws_,"in",ws_,Array,ws,")",ws,"(",ws,Body,ws,")"),
 1859        ['php','hack']:
 1860                ("foreach",ws,"(",ws,Array,ws_,"as",ws_,Var,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1861        ['java']:
 1862                ("for",ws,"(",ws,Type,ws_,Var,ws,":",ws,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1863        ['c#','vala']:
 1864                ("foreach",ws,"(",ws,Type,ws_,Var,ws_,"in",ws_,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1865        ['cython','python']:
 1866                ("for",python_ws_,Var,python_ws_,"in",python_ws_,Array,python_ws,":",python_ws,Body),
 1867        ['coffeescript']:
 1868                ("for",python_ws_,Var,python_ws_,"in",python_ws_,Array,python_ws,Body),
 1869        ['english_temp']:
 1870                (("for";"for",python_ws_,synonym("each")),python_ws_,Var,python_ws_,"in",python_ws_,Array,python_ws,":",python_ws,Body),
 1871        ['julia']:
 1872                ("for",ws_,Var,ws_,"in",ws_,Array,ws_,Body,(Indent;ws_),"end"),
 1873        ['chapel','swift']:
 1874                ("for",ws_,Var,ws_,"in",ws_,Array,ws,"{",ws,Body,(Indent;ws),"}"),
 1875        ['pawn']:
 1876                ("foreach",ws,"(",ws,"new",ws_,Var,ws,":",ws,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1877        ['picat']:
 1878                ("foreach",ws,"(",ws,Var,ws_,"in",ws_,Array,ws,")",ws,"(",ws,Body,ws,")",ws,"end"),
 1879        ['awk','ceylon']:
 1880                ("for",ws_,"(",ws_,Var,ws_,"in",ws_,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1881        ['go']:
 1882                ("for",ws_,Var,ws,":=",ws,"range",ws_,Array,ws,"{",ws,Body,(Indent;ws),"}"),
 1883        ['haxe','groovy']:
 1884                ("for",ws,"(",ws,Var,ws_,"in",ws_,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1885        ['nemerle','powershell']:
 1886                ("foreach",ws,"(",ws,Var,ws_,"in",ws_,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1887        ['scala']:
 1888                ("for",ws,"(",ws,Var,ws,"->",ws,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1889        ['rebol']:
 1890                ("foreach",ws_,Var,ws_,Array,ws,"[",ws,Body,ws,"]"),
 1891        ['c++']:
 1892                ("for",ws,"(",ws,Type,ws_,"&",ws_,Var,ws,":",ws,Array,ws,"){",ws,Body,(Indent;ws),"}"),
 1893        ['d']:
 1894                ("foreach",ws,"(",ws,Var,ws,",",ws,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 1895        ['gambas']:
 1896                ("FOR",ws_,"EACH",ws_,Var,ws_,"IN",ws_,Array,ws_,Body,ws_,"NEXT"),
 1897        ['vbscript','visual basic .net']:
 1898                ("For",ws_,"Each",ws_,Var,ws_,"In",ws_,Array,ws_,Body,ws_,"Next"),
 1899        ['dart']:
 1900                ("for",ws,"(",ws,"var",ws_,Var,ws_,"in",ws_,Array,ws,")",ws,"{",ws,Body,(Indent;ws),"}")
 1901        ]).
 1902
 1903switch_(Data,[A,B,Indent]) -->
 1904		langs_to_output(Data,switch,[
 1905		['rust']:
 1906				("match",ws_,A,ws,"{",ws,B,(Indent;ws),"}"),
 1907		['csh']:
 1908				("switch",ws,"(",ws,A,ws,")",ws_,B,(Indent;ws_),"endsw"),
 1909		['elixir']:
 1910				("case",ws_,A,ws_,"do",ws_,B,(Indent;ws_),"end"),
 1911		['scala']:
 1912				(A,ws_,"match",ws,"{",ws,B,(Indent;ws),"}"),
 1913		['octave']:
 1914				("switch",ws,"(",ws,A,ws,")",ws,B,(Indent;ws_),"endswitch"),
 1915		['java','d','powershell','nemerle','d','typescript','hack','swift','groovy','dart','awk','c#','javascript','c++','php','c','go','haxe','vala']:
 1916				("switch",ws,"(",!,ws,A,ws,")",ws,"{",!,ws,B,(Indent;ws),"}"),
 1917		['haskell','erlang']:
 1918				("case",ws_,A,ws_,"of",ws_,B,(Indent;ws_),"end"),
 1919		['delphi','pascal']:
 1920				("Case",ws_,A,ws_,"of",ws_,B,(Indent;ws_),"end;"),
 1921		['clips']:
 1922				("(",ws,"switch",ws_,A,ws_,B,ws,")"),
 1923		['visual basic']:
 1924				("Select",ws_,"Case",ws_,A,ws_,B,(Indent;ws_),"End",ws_,"Select"),
 1925		['rebol']:
 1926				("switch/default",ws,"[",ws,A,ws_,B,(Indent;ws_),"]"),
 1927		['fortran']:
 1928				("SELECT",ws_,"CASE",ws,"(",ws,A,ws,")",ws_,B,(Indent;ws_),"END",ws_,"SELECT"),
 1929		['clojure']:
 1930				("(",ws,"case",ws_,A,ws_,B,ws,")"),
 1931		['chapel']:
 1932				("select",ws,"(",ws,A,ws,")",ws,"{",ws,B,(Indent;ws),"}")
 1933        ]).
 1934
 1935unless_(Data,[A,B,Indent]) -->
 1936	langs_to_output(Data,unless,[
 1937		['english']:
 1938			("unless",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,":",python_ws,B),
 1939		['python','javascript','java','c#','prolog','c','c++','php','lua']:
 1940			if_without_else_(Data,[not_(Data,[A]),B,Indent]),
 1941		['ruby']:
 1942			("unless",ws_,A,ws_,B,(Indent;ws_),"end"),
 1943		['perl']:
 1944			("unless",ws,"(",ws,A,ws,")",ws,"{",ws,B,(Indent;ws_),"}")
 1945	]).
 1946        
 1947if_without_else_(Data,[A,B,Indent]) -->
 1948	langs_to_output(Data,if_without_else,[
 1949		['cython','python']:
 1950			("if",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,":",python_ws,B),
 1951		['java','e','ooc','englishscript','mathematical notation','polish notation','reverse polish notation','perl 6','chapel','katahdin','pawn','powershell','d','ceylon','typescript','actionscript','hack','autohotkey','gosu','nemerle','swift','nemerle','pike','groovy','scala','dart','javascript','c#','c','c++','perl','haxe','php','r','awk','vala','bc','squirrel']:
 1952			("if",ws,"(",ws,A,ws,")",ws,"{",ws,B,(Indent;ws),"}"),
 1953		['fortran']:
 1954				("IF",ws_,A,ws_,"THEN",ws_,B,(Indent;ws_),"END",ws_,"IF"),
 1955		['julia']:
 1956				("if",ws_,A,ws_,B,(Indent;ws_),"end"),
 1957		['picat','ruby','lua']:
 1958				("if",ws_,A,ws_,"then",ws_,B,(Indent;ws_),"end"),
 1959		['octave']:
 1960				("if",ws_,A,ws_,B,(Indent;ws_),"endif"),
 1961		['haskell','pascal','delphi','maxima','ocaml']:
 1962				("if",ws_,A,ws_,"then",ws_,B,ws_,C,ws_,D),
 1963		['livecode']:
 1964				("if",ws_,A,ws_,"then",ws_,B,(Indent;ws_),"end",ws_,"if"),
 1965		['vhdl']:
 1966				("if",ws_,A,ws_,"then",ws_,B,(Indent;ws_),"end",ws_,"if",ws,";"),
 1967		['rust','go']:
 1968				("if",ws_,A,ws,"{",ws,B,(Indent;ws),"}",(Indent;ws),C),
 1969		['clips']:
 1970				("(",ws,"if",ws_,A,ws_,"then",ws_,B,ws_,C,ws_,D,ws,")"),
 1971		['z3']:
 1972				("(",ws,"ite",ws_,A,ws_,B,ws_,C,ws_,D,ws,")"),
 1973		['minizinc']:
 1974				("if",ws_,A,ws_,"then",ws_,B,(Indent;ws_),"endif"),
 1975		['english']:
 1976				("if",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,":",python_ws,B),
 1977		['visual basic','visual basic .net']:
 1978				("If",ws_,A,ws_,"Then",ws_,B,(Indent;ws_),"End",ws_,"If"),
 1979		['monkey x']:
 1980				("if",ws_,A,ws_,B,(Indent;ws_),"EndIf")
 1981	]).
 1982
 1983if(Data,[A,B,C,D,Indent]) -->
 1984		langs_to_output(Data,if,[
 1985		['sympy']:
 1986				("Piecewise",ws,"(",ws,"(",ws,B,ws,",",ws,A,ws,")",ws,",",ws,C,ws,",",ws,D,ws,")"),
 1987		['erlang']:
 1988				("if",ws_,A,ws,"->",ws,B,ws,";",(Indent;ws),C,ws,";",(Indent;ws),D,(Indent;ws_),"end"),
 1989		['prolog','constraint handling rules','logtalk']:
 1990				("(",ws,A,ws,"->",ws,B,ws,";",(Indent;ws),C,ws,";",(Indent;ws),D,ws,")"),
 1991		['fortran']:
 1992				("IF",ws_,A,ws_,"THEN",ws_,B,ws_,C,ws_,D,(Indent;ws_),"END",ws_,"IF"),
 1993		['rebol']:
 1994				("case",ws,"[",ws,A,ws,"[",ws,B,ws,"]",ws,C,ws,D,ws,"]"),
 1995		['julia']:
 1996				("if",ws_,A,ws_,B,ws_,C,ws_,D,(Indent;ws_),"end"),
 1997		['picat','ruby','lua']:
 1998				("if",ws_,A,ws_,"then",ws_,B,ws_,C,ws_,D,(Indent;ws_),"end"),
 1999		['octave']:
 2000				("if",ws_,A,ws_,B,ws_,C,ws_,D,(Indent;ws_),"endif"),
 2001		['haskell','pascal','delphi','maxima','ocaml']:
 2002				("if",ws_,A,ws_,"then",ws_,B,ws_,C,ws_,D),
 2003		['livecode']:
 2004				("if",ws_,A,ws_,"then",ws_,B,(Indent;ws_),C,ws_,D,(Indent;ws_),"end",ws_,"if"),
 2005		['vhdl']:
 2006				("if",ws_,A,ws_,"then",ws_,B,ws_,C,ws_,D,(Indent;ws_),"end",ws_,"if",ws,";"),
 2007		['java','e','ooc','englishscript','mathematical notation','polish notation','reverse polish notation','perl 6','chapel','katahdin','pawn','powershell','d','ceylon','typescript','actionscript','hack','autohotkey','gosu','nemerle','swift','nemerle','pike','groovy','scala','dart','javascript','c#','c','c++','perl','haxe','php','r','awk','vala','bc','squirrel']:
 2008				(if_without_else_(Data,[A,B,Indent]),(Indent;ws),C,(Indent;ws),D),
 2009		['rust','go']:
 2010				("if",ws_,A,ws,"{",ws,B,(Indent;ws),"}",(Indent;ws),C),
 2011		['clips']:
 2012				("(",ws,"if",ws_,A,ws_,"then",ws_,B,ws_,C,ws_,D,ws,")"),
 2013		['z3']:
 2014				("(",ws,"ite",ws_,A,ws_,B,ws_,C,ws_,D,ws,")"),
 2015		['minizinc']:
 2016				("if",ws_,A,ws_,"then",ws_,B,ws_,C,ws_,D,(Indent;ws_),"endif"),
 2017		['cython','python']:
 2018				(if_without_else_(Data,[A,B,Indent]),python_ws,Indent,C,D),
 2019		['english_temp']:
 2020				("if",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,":",python_ws,B,python_ws,Indent,C,D),
 2021		['visual basic','visual basic .net']:
 2022				("If",ws_,A,ws_,"Then",ws_,B,ws_,C,ws_,D,(Indent;ws_),"End",ws_,"If"),
 2023		['common lisp']:
 2024				("(",ws,"cond",ws,"(",ws,A,ws_,B,ws,")",ws_,C,ws_,D,ws,")"),
 2025		['wolfram']:
 2026				("If",ws,"[",ws,A,ws,",",ws,B,ws,",",ws,C,(Indent;ws),"]"),
 2027		['polish notation']:
 2028				("if",ws_,A,ws_,B),
 2029		['reverse polish notation']:
 2030				(A,ws_,B,ws_,"if"),
 2031		['monkey x']:
 2032				("if",ws_,A,ws_,B,ws_,C,(Indent;ws_),"EndIf")
 2033        ]).
 2034
 2035do_while_(Data,[Condition,Body,Indent]) -->
 2036        langs_to_output(Data,do_while,[
 2037        ['javascript','actionscript','java','c','php','d','c++','c#','perl']:
 2038			("do",ws,"{",!,ws,Body,(Indent;ws),"}",ws,"while",ws,"(",ws,Condition,ws,")",ws,";"),
 2039		['kotlin']:
 2040			("do",ws,"{",ws,Body,(Indent;ws),"}",ws,"while",ws,"(",ws,Condition,ws,")"),
 2041		['swift']:
 2042			("repeat",ws,"{",ws,Body,(Indent;ws),"}",ws,"while",(ws_,Condition;ws,"(",ws,Condition,ws,")")),
 2043		['visual basic .net']:
 2044			("Do",ws_,Body,(Indent;ws_),"Loop",ws_,"While",ws,Condition),
 2045		['ruby']:
 2046			("begin",ws_,Body,(Indent;ws_),"end",ws_,"while",ws,Condition),
 2047		['lua']:
 2048			("repeat",ws_,Body,(Indent;ws_),"until",ws,"(",ws,Condition,ws,")")
 2049]).
 2050
 2051map_(Data,[Func,Arr]) -->
 2052        langs_to_output(Data,map,[
 2053			['common lisp']:
 2054				("(",ws,"mapcar",ws_,Func,ws_,Arr,ws,")"),
 2055			['clojure','haskell']:
 2056				("(",ws,"map",ws_,Func,ws_,Arr,ws,")"),
 2057			['groovy']:
 2058				(Arr,ws,".",ws,"collect",ws,"(",ws,Func,ws,")"),
 2059			['python']:
 2060				("map",python_ws,"(",python_ws,Func,python_ws,",",python_ws,Arr,python_ws,")"),
 2061			['php']:
 2062				("array_map",ws,"(",ws,Func,ws,",",ws,Arr,ws,")")
 2063]).
 2064
 2065while_(Data,[A,B,Indent]) -->
 2066        langs_to_output(Data,while,[
 2067        ['c','perl 6','katahdin','chapel','ooc','processing','pike','kotlin','pawn','powershell','hack','gosu','autohotkey','ceylon','d','typescript','actionscript','nemerle','dart','swift','groovy','scala','java','javascript','php','c#','perl','c++','haxe','r','awk','vala']:
 2068                ("while",ws,"(",ws,A,ws,")",ws,"{",!,ws,B,(Indent;ws),"}"),
 2069        ['ocaml']:
 2070				("while",ws_,A,ws_,"do",ws_,B,(Indent;ws_),"done"),
 2071        ['gap']:
 2072                ("while",ws_,A,ws_,"do",ws_,B,(Indent;ws_),"od",ws,";"),
 2073        ['ruby','lua']:
 2074                ("while",ws_,A,ws_,"do",ws_,B,(Indent;ws_),"end"),
 2075        ['fortran']:
 2076                ("WHILE",ws_,"(",ws,A,ws,")",ws_,"DO",ws_,B,(Indent;ws_),"ENDDO"),
 2077        ['pascal']:
 2078                ("while",ws_,A,ws_,"do",ws_,"begin",ws_,B,(Indent;ws_),"end;"),
 2079        ['delphi']:
 2080                ("While",ws_,A,ws_,"do",ws_,"begin",ws_,B,(Indent;ws_),"end;"),
 2081        ['rust','frink','dafny']:
 2082                ("while",ws_,A,ws,"{",ws,B,(Indent;ws),"}"),
 2083        ['julia']:
 2084                ("while",ws_,A,ws_,B,(Indent;ws_),"end"),
 2085        ['picat']:
 2086                ("while",ws_,"(",ws,A,ws,")",ws_,B,(Indent;ws_),"end"),
 2087        ['rebol']:
 2088                ("while",ws,"[",ws,A,ws,"]",ws,"[",ws,B,ws,"]"),
 2089        ['common lisp']:
 2090                ("(",ws,"loop",ws_,"while",ws_,A,ws_,"do",ws_,B,ws,")"),
 2091        ['hy','newlisp','clips']:
 2092                ("(",ws,"while",ws_,A,ws_,B,ws,")"),
 2093        ['cython','python']:
 2094                ("while",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,":",B),
 2095        ['coffeescript']:
 2096                ("while",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,B),
 2097        ['english']:
 2098                ("while",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,":",B),
 2099        ['visual basic','visual basic .net','vbscript']:
 2100                ("While",ws_,A,ws_,B,(Indent;ws_),"End",ws_,"While"),
 2101        ['octave']:
 2102                ("while",ws,"(",ws,A,ws,")",ws_,B,(Indent;ws_),"endwhile"),
 2103        ['wolfram']:
 2104                ("While",ws,"[",ws,A,ws,",",ws,B,(Indent;ws),"]"),
 2105        ['go']:
 2106                ("for",ws_,A,ws,"{",ws,B,(Indent;ws),"}"),
 2107        ['vbscript']:
 2108                ("Do",ws_,"While",ws_,A,ws_,B,(Indent;ws_),"Loop"),
 2109        ['seed7']:
 2110                ("while",ws_,A,ws_,"do",ws_,B,(Indent;ws_),"end",ws_,"while",ws,";"),
 2111        ['vhdl']:
 2112				("while",ws_,A,ws_,"loop",ws_,B,(Indent;ws_),"end",ws_,"loop",ws,";")
 2113        ]),!.
 2114
 2115predicate_(Data,[Name,Params,Body,_]) -->
 2116		%add predicates for python and clips
 2117		langs_to_output(Data,predicate,[
 2118		['prolog']:
 2119			(Name,ws,"(",ws,Params,ws,")",ws,":-",ws,Body),
 2120		['minizinc']:
 2121			("predicate",ws_,Name,ws,"(",ws,Params,ws,")",ws,"=",ws,Body),
 2122		%this is for pydatalog
 2123		['cosmos']:
 2124			("rel",python_ws_,Name,python_ws,"(",python_ws,Params,python_ws,")",python_ws,Body,python_ws)
 2125		]).
 2126
 2127iff_(Data,[Condition,Body]) -->
 2128        langs_to_output(Data,iff,[
 2129        ['z3']:
 2130			("(",ws,("iff";"<=>"),ws_,Condition,ws_,Body,ws_,")"),
 2131		['minizinc']:
 2132			(Condition,ws,"<->",ws,Body)
 2133        ]).
 2134
 2135for_(Data,[Statement1,Condition,Statement2,Body,Indent]) -->
 2136		langs_to_output(Data,for,[
 2137        ['java','d','pawn','groovy','javascript','dart','typescript','php','hack','c#','perl','c++','awk','pike']:
 2138                ("for",ws,"(",!,ws,Statement1,ws,";",ws,Condition,ws,";",ws,Statement2,ws,")",ws,"{",!,ws,Body,(Indent;ws),"}")
 2139        ]).
 2140
 2141semicolon_(Data,[A]) -->
 2142		{grammars(Grammars)},
 2143        langs_to_output(Data,semicolon,[
 2144        Grammars:
 2145				A,
 2146        ['c','hack','vhdl','f#','php','dafny','chapel','katahdin','frink','falcon','aldor','idp','processing','maxima','seed7','drools','engscript','openoffice basic','ada','algol 68','d','ceylon','rust','typescript','octave','autohotkey','pascal','delphi','javascript','pike','objective-c','ocaml','java','scala','dart','php','c#','c++','haxe','awk','bc','perl','perl 6','nemerle','vala']:
 2147                (A,ws,";",!),
 2148        ['pseudocode']:
 2149                (A,("";ws,";")),
 2150        ['visual basic .net','clips','pddl','sympy','r','constraint handling rules','pydatalog','common lisp','gnu smalltalk','ruby','lua','hy',picolisp,logtalk,minizinc,'swift','rebol','fortran','go','picat','julia',prolog,'haskell','mathematical notation','erlang',z3]:
 2151                A,
 2152		['python','cython','coffeescript']:
 2153				(A;A,";"),
 2154		['english']:
 2155				(A;A,";")
 2156        ]).
 2157
 2158
 2159class_implements_interface_(Data,[C1,C2,B,Indent]) -->
 2160        langs_to_output(Data,class_implements_interface,[
 2161        ['java','c#']:
 2162                ("public",ws_,"class",ws_,C1,ws_,"implements",ws_,C2,ws,"{",ws,B,(Indent;ws),"}")
 2163        ]).
 2164
 2165class_extends_and_implements_(Data,[C1,C2,C3,B,Indent]) -->
 2166        langs_to_output(Data,class_extends_and_implements,[
 2167        ['java','c#']:
 2168			("public",ws_,"class",ws_,C1,ws_,"extends",ws_,C2,ws_,"implements",ws_,C3,ws,"{",ws,B,(Indent;ws),"}"),
 2169        ['php']:
 2170			("class",ws_,C1,ws_,"extends",ws_,C2,ws_,"implements",ws_,C3,ws,"{",ws,B,(Indent;ws),"}")
 2171        ]).
 2172
 2173interface_extends_(Data,[C1,C2,B,Indent]) -->
 2174        langs_to_output(Data,interface_extends,[
 2175        ['java','c#']:
 2176			("public",ws_,"interface",ws_,C1,ws_,"extends",ws_,C2,ws,"{",ws,B,(Indent;ws),"}"),
 2177		['php']:
 2178			("interface",ws_,C1,ws_,"extends",ws_,C2,ws,"{",ws,B,(Indent;ws),"}"),
 2179		['swift']:
 2180			("protocol",ws_,C1,ws,":",ws,C2,ws,"{",ws,B,(Indent;ws),"}")
 2181		]).
 2182
 2183class_extends_(Data,[C1,C2,B,Indent]) -->
 2184        langs_to_output(Data,class_extends,[
 2185        ['logtalk']:
 2186                ("object",ws,"(",C1,ws,",",ws,"extends",ws,"(",ws,C2,ws,")",ws,".",ws,B,(Indent;ws),"end_object",ws,"."),
 2187        ['hy']:
 2188                ("(",ws,"defclass",ws_,C1,ws_,"[",ws,C2,ws,"]",ws_,B,")"),
 2189        ['swift','chapel','d','swift']:
 2190                ("class",ws_,C1,ws,":",ws,C2,ws,"{",ws,B,(Indent;ws),"}"),
 2191        ['haxe','php','javascript','dart','typescript']:
 2192                ("class",ws_,C1,ws_,"extends",!,ws_,C2,ws,"{",!,ws,B,(Indent;ws),"}"),
 2193        ['java','c#','scala']:
 2194                ("public",ws_,"class",ws_,C1,ws_,"extends",ws_,C2,ws,"{",ws,B,(Indent;ws),"}"),
 2195        ['c']:
 2196                ("#include",ws_,"'",ws,C2,ws,".h'",ws_,B),
 2197        ['c++']:
 2198                ("class",ws_,C1,ws,":",ws,"public",ws_,C2,ws,"{",ws,B,(Indent;ws),"}"),
 2199        ['perl 6']:
 2200                ("class",ws_,C1,ws_,"is",ws_,C2,ws,"{",ws,B,(Indent;ws),"}"),
 2201        ['monkey x']:
 2202                ("Class",ws_,C1,ws_,"Extends",ws_,C2,ws_,B,(Indent;ws_),"End"),
 2203        ['ruby']:
 2204				("class",ws_,C1,ws_,"<<",ws_,C2,ws_,Body,(Indent;ws_),"end")
 2205        ]).
 2206
 2207abstract_class_(Data,[Name,Body,Indent]) -->
 2208		langs_to_output(Data,abstract_class,[
 2209			['java','c#']:
 2210                ("public",ws_,"abstract",ws_,"class",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}"),
 2211            ['php']:
 2212                ("abstract",ws_,"class",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}")
 2213        ]).
 2214
 2215interface_(Data,[Name,Body,Indent]) -->
 2216		langs_to_output(Data,interface,[
 2217			['java','c#']:
 2218                ("public",ws_,"interface",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}"),
 2219            ['php']:
 2220                ("interface",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}"),
 2221            ['swift']:
 2222                ("protocol",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}"),
 2223            ['go']:
 2224                ("type",ws_,Name,ws_,"interface",ws,"{",ws,Body,(Indent;ws),"}")
 2225        ]).
 2226
 2227interface_method_(Data,[Name,Type,Params,Indent]) -->
 2228	langs_to_output(Data,interface_method,[
 2229		['java','c#']:
 2230			(Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,";"),
 2231		['go']:
 2232			(Name,ws,"(",ws,Params,ws,")",ws_,Type),
 2233		['php']:
 2234			("public",ws_,"function",ws_,Name,ws,"(",ws,Params,ws,")",ws,";"),
 2235		['swift']:
 2236			("func",ws_,Name,ws,"(",Params,ws,")",ws,"->",ws,Type)
 2237	]).
 2238
 2239class_(Data,[Name,Body,Indent]) -->
 2240		langs_to_output(Data,class,[
 2241		['julia']:
 2242                ("type",ws_,Name,ws_,Body,(Indent;ws_),"end"),
 2243        ['ruby']:
 2244                ("class",ws_,Name,ws_,Body,(Indent;ws_),"end"),
 2245        ['java','c#']:
 2246                ("public",ws_,"class",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}"),
 2247        ['hy']:
 2248                ("(",ws,"defclass",ws_,Name,ws_,"[",ws,"object",ws,"]",ws_,Body,")"),
 2249        ['perl']:
 2250                ("package",ws_,Name,";",ws,Body),
 2251        ['c++']:
 2252                ("class",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}",ws,";"),
 2253        ['logtalk']:
 2254                ("object",ws,"(",Name,")",ws,".",ws,Body,(Indent;ws),"end_object",ws,"."),
 2255        ['javascript','hack','php','scala','haxe','chapel','swift','d','typescript','dart','perl 6']:
 2256                ("class",ws_,Name,ws,"{",!,ws,Body,(Indent;ws),"}"),
 2257        ['vbscript']:
 2258                ("Public",ws_,"Class",ws_,Name,ws_,Body,(Indent;ws_),"End",ws_,"Class"),
 2259        ['monkey x']:
 2260                ("Class",ws_,Name,ws_,Body,(Indent;ws_),"End"),
 2261        ['python']:
 2262				("class",python_ws_,Name,python_ws,"(",python_ws,"object",python_ws,")",python_ws,":",Body)
 2263        ]).
 2264
 2265
 2266function_(Data,[Name,Type,Params,Body,Indent]) -->
 2267		langs_to_output(Data,function,[
 2268		['coffeescript']:
 2269				(
 2270					Name,python_ws,"=",python_ws,"(",python_ws,Params,python_ws,")",python_ws,"->",python_ws,Body;
 2271					{Params = parameters(_,[])}, Name,python_ws,"=",python_ws,"->",python_ws,Body
 2272				),
 2273		['parboiled']:
 2274				("Rule",ws_,Name,ws,"(",ws,")",ws,"{",ws,"return",ws_,Body,ws,";",!,ws_,"}"),
 2275		['antlr']:
 2276				(Name,ws,":",ws,Body,";"),
 2277		['peg.js','lpeg','abnf']:
 2278				(Name,ws,"=",ws,Body),
 2279		['wirth syntax notation']:
 2280				(Name,ws,"=",ws,Body,ws,"."),
 2281		['marpa']:
 2282				(Name,ws,"::=",ws,Body),
 2283		['waxeye']:
 2284				(Name,ws,"<-",ws,Body),
 2285		['nearley']:
 2286				(Name,ws,"[",ws,Params,ws,"]",ws,"->",ws,Body),
 2287		['definite clause grammars']:
 2288				(Name,ws,"(",ws,Params,ws,")",ws,"-->",ws,Body,ws,"."),
 2289		['c++','vala','c','dart','ceylon','pike','d','englishscript']:
 2290                (Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 2291		['systemverilog']:
 2292				("function",ws_,Name,ws,"(",ws,Params,ws,");",ws,Body,(Indent;ws),"endfunction"),
 2293        ['vhdl']:
 2294				("function",ws_,Name,ws,"(",ws,Params,ws,")",ws_,"return",ws_,Type,ws_,"is",ws_,"begin",ws_,Body,(Indent;ws_),"end",ws_,Name,ws,";"),
 2295		['python','cython']:
 2296				("def",python_ws_,Name,"(",Params,")",":",python_ws,Body),
 2297		['english']:
 2298				(("def";"func";"function"),python_ws_,Name,"(",Params,(")",python_ws,":";")"),python_ws,Body),
 2299		['sympy']:
 2300				("def",python_ws_,Name,"(",Params,")",":",python_ws,"return",python_ws_,Body),
 2301		['cobra']:
 2302				("def",python_ws_,Name,"(",Params,")",python_ws,Body),
 2303		['sql']:
 2304                ("CREATE",ws_,"FUNCTION",ws_,"dbo",ws,".",ws,Name,ws,"(",ws,"function_parameters",ws,")",ws_,"RETURNS",ws_,Type,ws_,Body),
 2305        ['hy']:
 2306				("(",ws,"defn",ws_,Name,ws_,"[",ws,Params,ws,"]",ws_,Body,ws,")"),
 2307        ['seed7']:
 2308                ("const",ws_,"func",ws_,Type,ws,":",ws,Name,ws,"(",ws,Params,ws,")",ws_,"is",ws_,"func",ws_,"begin",ws_,Body,(Indent;ws_),"end",ws_,"func",ws,";"),
 2309        ['livecode']:
 2310                ("function",ws_,Name,ws_,Params,ws_,Body,(Indent;ws_),"end",ws_,Name),
 2311        ['monkey x']:
 2312                ("Function",ws,Name,ws,":",ws,Type,ws,"(",ws,Params,ws,")",ws,Body,(Indent;ws_),"End"),
 2313        ['emacs lisp']:
 2314                ("(",ws,"defun",ws_,Name,ws_,"(",ws,Params,ws,")",ws_,Body,ws,")"),
 2315        ['go']:
 2316                ("func",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2317        ['pydatalog']:
 2318                (Name,ws,"[",ws,Params,ws,"]",ws,"<=",ws,Body),
 2319        ['java','c#']:
 2320                ("public",ws_,"static",ws_,Type,ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 2321        ['javascript','php']:
 2322                ("function",ws_,Name,ws,"(",!,ws,Params,ws,")",ws,"{",!,ws,Body,(Indent;ws),"}"),
 2323        ['julia','lua']:
 2324                ("function",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Body,(Indent;ws_),"end"),
 2325        ['wolfram']:
 2326                (Name,ws,"[",ws,Params,ws,"]",ws,":=",ws,Body),
 2327        ['frink']:
 2328                (Name,ws,"[",ws,Params,ws,"]",ws,":=",ws,"{",ws,Body,(Indent;ws),"}"),
 2329        ['pop-11']:
 2330                ("define",ws_,Name,ws,"(",ws,Params,ws,")",ws,"->",ws,"Result;",ws_,Body,(Indent;ws_),"enddefine;"),
 2331        ['z3']:
 2332                ("(",ws,"define-fun",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Type,ws_,Body,ws,")"),
 2333        ['mathematical notation']:
 2334                (Name,ws,"(",ws,Params,ws,")",ws,"=",ws,"{",ws,Body,(Indent;ws),"}"),
 2335        ['chapel']:
 2336                ("proc",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2337        ['prolog',logtalk]:
 2338                ({Params = ""} -> (Name,ws,"(",ws,"Return",ws,")",ws_,":-",ws_,Body); (Name,ws,"(",ws,"(",ws,Params,ws,")",ws,",",ws,"Return",ws,")",ws_,":-",ws_,Body)),
 2339		['constraint handling rules']:
 2340                ({Params = ""} -> (":- chr_constraint",ws_,Name,"/1",ws,".",ws_,Name,ws,"(",ws,"Return",ws,")",ws,"\\",Name,ws,"(",ws,"Return",ws,")","<=>true.",ws_,Name,ws,"(",ws,"Return",ws,")",ws_,"<=>",ws_,Body); (":- chr_constraint",ws_,Name,"/2",ws,".",ws_,Name,ws,"(",ws,"A",ws,",",ws,"B",ws,")",ws,"\\",ws,Name,ws,"(",ws,"A",ws,",",ws,"B",ws,")",ws_,"<=>",ws,"true",ws,".",ws_,Name,ws,"(",ws,"(",ws,Params,ws,")",ws,",",ws,"Return",ws,")",ws_,"<=>",ws_,Body)),
 2341        ['picat']:
 2342                (Name,ws,"(",ws,Params,ws,")",ws,"=",ws,"retval",ws,"=>",ws,Body),
 2343        ['swift']:
 2344                ("func",ws_,Name,ws,"(",ws,Params,ws,")",ws,"->",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2345        ['maxima']:
 2346                (Name,ws,"(",ws,Params,ws,")",ws,":=",ws,Body),
 2347        ['rust']:
 2348                ("fn",ws_,Name,ws,"(",ws,Params,ws,")",ws,"->",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2349        ['clojure']:
 2350                ("(",ws,"defn",ws,Name,ws,"[",ws,Params,ws,"]",ws,Body,ws,")"),
 2351        ['octave']:
 2352                ("function",ws_,"retval",ws,"=",ws,Name,ws,"(",ws,Params,ws,")",ws,Body,(Indent;ws_),"endfunction"),
 2353        ['haskell']:
 2354                (Name,python_ws_,Params,python_ws,"=",python_ws,"return",python_ws_,"where",python_ws,Body),
 2355        ['common lisp']:
 2356                ("(",ws,"defun",ws_,Name,ws,"(",ws,Params,ws,")",ws,Body,ws,")"),
 2357        ['fortran']:
 2358                ("FUNC",ws_,Name,ws_,"(",ws,Params,ws,")",ws_,"RESULT",ws,"(",ws,"retval",ws,")",ws_,Type,ws,"::",ws,"retval",ws_,Body,(Indent;ws_),"END",ws_,"FUNCTION",ws_,Name),
 2359        ['scala']:
 2360                ("def",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,"=",ws,"{",ws,Body,(Indent;ws),"}"),
 2361        ['minizinc']:
 2362                ("function",ws_,Type,ws,":",ws,Name,ws,"(",ws,Params,ws,")",ws,"=",ws,Body),
 2363        ['clips']:
 2364                ("(",ws,"deffunction",ws_,Name,ws,"(",ws,Params,ws,")",ws,Body,ws,")"),
 2365        ['erlang']:
 2366                (Name,ws,"(",ws,Params,ws,")",ws,"->",ws,Body),
 2367        ['perl']:
 2368				(("sub",ws_,Name,ws,"{",ws,"my",ws,"(",Params,")",ws,"=@_",ws,";",!,ws,Body,(Indent;ws),"}")),
 2369        ['perl 6']:
 2370                ("sub",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 2371        ['pawn']:
 2372                (Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 2373        ['ruby']:
 2374				(
 2375					"def",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Body,(Indent;ws_),"end";
 2376					{Params = parameters(_,[])},"def",ws_,Name,ws_,Body,(Indent;ws_),"end"
 2377				),
 2378        ['typescript']:
 2379                ("function",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2380        ['rebol']:
 2381                (Name,ws,":",ws_,"func",ws,"[",ws,Params,ws,"]",ws,"[",ws,Body,ws,"]"),
 2382        ['haxe']:
 2383                ("public",ws_,"static",ws_,"function",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2384        ['hack']:
 2385                ("function",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2386        ['r']:
 2387                (Name,ws,"<-",ws,"function",ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 2388        ['bc']:
 2389                ("define",ws_,Name,ws,"(",ws,Params,ws,")",ws,"{",ws,Body,(Indent;ws),"}"),
 2390        ['visual basic','visual basic .net']:
 2391                ("Function",ws_,Name,ws,"(",ws,Params,ws,")",ws_,"As",ws_,Type,ws_,Body,(Indent;ws_),"End",ws_,"Function"),
 2392        ['vbscript']:
 2393                ("Function",ws_,Name,ws,"(",ws,Params,ws,")",ws_,Body,(Indent;ws_),"End",(Indent;ws_),"Function"),
 2394        ['racket','newlisp']:
 2395                ("(define",ws,"(name",ws,"params)",ws,Body,ws,")"),
 2396        ['janus']:
 2397                ("procedure",ws_,Name,ws,"(",ws,Params,ws,")",ws,Body),
 2398        ['cosmos']:
 2399                ("rel",python_ws_,Name,python_ws,"(",python_ws,Params,python_ws,",",python_ws,"return",python_ws,")",python_ws,Body),
 2400        ['f#']:
 2401                ("let",python_ws_,Name,python_ws_,Params,python_ws,"=",Body),
 2402        ['polish notation']:
 2403                ("=",ws,Name,ws,"(",ws,Params,ws,")",ws_,Body),
 2404        ['reverse polish notation']:
 2405                (Name,ws,"(",ws,Params,ws,")",ws_,Body,ws_,"="),
 2406        ['ocaml']:
 2407                ("let",ws_,Name,ws_,Params,ws,"=",ws,Body),
 2408        ['e']:
 2409                ("def",ws_,Name,ws,"(",ws,Params,ws,")",ws,Type,ws,"{",ws,Body,(Indent;ws),"}"),
 2410        ['pascal','delphi']:
 2411                ("function",ws_,Name,ws,"(",ws,Params,ws,")",ws,":",ws,Type,ws,";",!,ws,"begin",ws_,Body,(Indent;ws_),"end",ws,";")
 2412        ]).
 2413
 2414reserved_words(A) :-
 2415	forall(member(B,["end","sin","cos","tan","abs","type","writeln","indexOf","charAt","gets","sample","array","readline","array_rand","input","random","choice","randrange","list","print","print_int","print_string","String","string","int","sort","sorted","reverse","sha1","reversed","len","unique_everseen","True","Number","float","double","return","def","str","char","boolean","function","false","true","enumerate"]),dif(A,B)).
 2416
 2417var_name_(Data,Type,A) -->
 2418        {Data = [Lang|_],reserved_words(A)},
 2419        ({memberchk(Lang,['python','english','engscript','abnf','wirth syntax notation','marpa','antlr','definite clause grammars','peg.js', 'systemverilog', 'vhdl', 'visual basic .net', 'ruby', 'lua', 'cosmos', 'englishscript','vbscript','polish notation','reverse polish notation','wolfram','pseudocode','mathematical notation','pascal','katahdin','typescript','javascript','frink','minizinc','aldor','flora-2','f-logic','d','genie','ooc','janus','chapel','abap','cobol','picolisp','rexx','pl/i','falcon','idp','processing','sympy','maxima','z3','shen','ceylon','nools','pyke','self','gnu smalltalk','elixir','lispyscript','standard ml','nim','occam','boo','seed7','pyparsing','agda','icon','octave','cobra','kotlin','c++','drools','oz','pike','delphi','racket','ml','java','pawn','fortran','ada','freebasic','matlab','newlisp','hy','ocaml','julia','autoit','c#','gosu','autohotkey','groovy','rust','r','swift','vala','go','scala','nemerle','visual basic','clojure','haxe','coffeescript','dart','javascript','c#','haskell','c','gambas','common lisp','scheme','rebol','f#'])}->
 2420                symbol(A);
 2421        {memberchk(Lang,['php','perl','bash','tcl','autoit','perl 6','puppet','hack','awk','powershell'])}->
 2422                ({Lang='perl',Type=[array,_]}->
 2423                    "@",symbol(A);
 2424                {Lang='perl',Type=[dict,_]}->
 2425                    "%",symbol(A);
 2426                "$",symbol(A));
 2427        {memberchk(Lang,[prolog,'constraint handling rules','erlang','picat',logtalk,pydatalog]),atom_string(B,A), first_char_uppercase(B, C),atom_chars(C,D)}->
 2428            symbol(D);
 2429        {memberchk(Lang,['lpeg'])}->
 2430			("lpeg.V\"",A,"\"");
 2431		{memberchk(Lang,['pddl','clips'])}->
 2432			("?",A);
 2433        {memberchk(Lang,['nearley'])}->
 2434            ("$",symbol(A));
 2435        {memberchk(Lang,['parboiled'])}->
 2436            (symbol(A),"()");
 2437        {not_defined_for(Data,'var_name')}),
 2438        {is_var_type(Data, A, Type)},!.
 2439
 2440else(Data,[Indent,A]) -->
 2441        langs_to_output(Data,else,[
 2442        ['sympy']:
 2443				("(",ws,A,ws,",",ws,"True",ws,")"),
 2444        ['clojure']:
 2445                (":else",ws_,A),
 2446        ['fortran']:
 2447                ("ELSE",ws_,A),
 2448        ['hack','e','ooc','englishscript','mathematical notation','dafny','perl 6','frink','chapel','katahdin','pawn','powershell','puppet','ceylon','d','rust','typescript','scala','autohotkey','gosu','groovy','java','swift','dart','awk','javascript','haxe','php','c#','go','perl','c++','c','tcl','r','vala','bc']:
 2449                ("else",ws,"{",!,ws,A,(Indent;ws),"}"),
 2450        ['seed7','vhdl','ruby','lua','livecode','janus','haskell','clips','minizinc','julia','octave','picat','pascal','delphi','maxima','ocaml','f#']:
 2451                ("else",ws_,A),
 2452        ['erlang']:
 2453                ("true",ws,"->",ws,A),
 2454        ['wolfram','prolog']:
 2455                (A),
 2456        ['z3']:
 2457                (A),
 2458        ['cython','python']:
 2459                (Indent,"else",python_ws,":",!,python_ws,A),
 2460        ['english_temp']:
 2461                (Indent,"else",python_ws,":",python_ws,A),
 2462        ['monkey x','vbscript','visual basic .net']:
 2463                ("Else",ws_,A),
 2464        ['rebol']:
 2465                ("true",ws,"[",ws,A,ws,"]"),
 2466        ['common lisp']:
 2467                ("(",ws,"t",ws_,A,ws,")"),
 2468        ['pseudocode']:
 2469                (("otherwise",ws_,A);
 2470                ("else",ws_,A);
 2471                ("else",ws,"{",!,ws,A,(Indent;ws),"}")),
 2472        ['polish notation']:
 2473                ("else",ws_,A),
 2474        ['reverse polish notation']:
 2475                (A,ws_,"else")
 2476        ]).
 2477
 2478enum_list_separator(Data) -->
 2479        langs_to_output(Data,enum_list_separator,[
 2480        ['pseudocode']:
 2481                (",";";"),
 2482        ['java','seed7','vala','c++','c#','c','typescript','fortran','ada','scala']:
 2483                ",",
 2484        ['haxe']:
 2485                ";",
 2486        ['go','perl 6','swift']:
 2487                ws_
 2488        ]).
 2489
 2490parameter_separator(Data) -->
 2491        langs_to_output(Data,parameter_separator,[
 2492        ['hy','ocaml','f#','polish notation','reverse polish notation','z3','scheme','racket','common lisp','clips','rebol','haskell','racket','clojure']:
 2493                ws_,
 2494        ['pseudocode','english','ruby','definite clause grammars','nearley','sympy','systemverilog','vhdl','visual basic .net','perl','constraint handling rules','lua','ruby','python','javascript','logtalk','nim','seed7','pydatalog','e','vbscript','monkey x','livecode','ceylon','delphi','englishscript','cython','vala','dafny','wolfram','gambas','d','frink','chapel','swift','perl 6','janus','mathematical notation','pascal','rust','picat','autohotkey','maxima','octave','julia','r','prolog','fortran','go','minizinc','erlang','coffeescript','php','hack','java','c#','c','c++','typescript','dart','haxe','scala','visual basic']:
 2495                ","
 2496        ]).
 2497        
 2498same_value_separator(Data) -->
 2499        langs_to_output(Data,same_value_separator,[
 2500        ['java','c#','perl']:
 2501			"=",
 2502		['haxe']:
 2503			","
 2504        ]).
 2505
 2506varargs_(Data,[Type,Name]) -->
 2507    langs_to_output(Data,varargs,[
 2508    ['java']:
 2509        (Type,ws,"...",ws_,Name),
 2510    ['php']:
 2511        ("",ws,Type,ws,"...",ws_,"$",ws,Name),
 2512    ['c#']:
 2513        ("params",ws_,Type,ws,"[",ws,"]",ws_,Name),
 2514    ['perl 6']:
 2515        ("*@",Name),
 2516    ['scala']:
 2517        (Name,ws,":",ws,Type,ws,"*"),
 2518    ['go']:
 2519        (Name,ws,"...",ws,Type)
 2520    ]).
 2521
 2522reference_parameter_(Data,[Type,Name]) -->
 2523	langs_to_output(Data,reference_parameter,[
 2524		['php']:
 2525            ("&",Name),
 2526        ['c#']:
 2527            ("ref",ws_,Type,ws_,Name),
 2528        ['visual basic']:
 2529			("ByRef",ws_,Name,ws_,"As",ws_,Double),
 2530		['c++']:
 2531            (Type,ws_,"&",Name)
 2532	]).
 2533
 2534parameter_(Data,[Type,Name]) -->
 2535        langs_to_output(Data,parameter,[
 2536        ['pseudocode']:
 2537                (("in",ws_,Type,ws,":",ws,Name;
 2538                Type,ws_,Name;
 2539                Name,ws,":",ws,Type;
 2540                Name,ws_,Type;
 2541                "var",ws_,Type,ws,":",ws,Name;
 2542                Name,ws,"::",ws,Type;
 2543                Type,ws,"[",ws,Name,ws,"]";
 2544                Name,ws_,("As";"as"),ws_,Type)),
 2545        ['seed7']:
 2546            ("in",ws_,Type,ws,":",ws,Name),
 2547        ['c#','systemverilog','java','englishscript','ceylon','algol 68','groovy','d','c++','pawn','pike','vala','c','janus']:
 2548            (Type,ws_,Name),
 2549        ['haxe','vhdl','dafny','chapel','pascal','rust','genie','hack','nim','typescript','gosu','delphi','nemerle','scala','swift']:
 2550            (Name,ws,":",ws,Type),
 2551        ['go','sql']:
 2552            (Name,ws_,Type),
 2553        ['minizinc']:
 2554            ("var",ws_,Type,ws,":",ws,Name),
 2555        ['haskell','definite clause grammars','nearley','sympy','pydatalog','python','english','ruby','lua','hy','perl 6','cosmos','polish notation','reverse polish notation','scheme','mathematical notation','lispyscript','clips','clojure','f#','ml','racket','ocaml','tcl','common lisp','newlisp','cython','frink','picat','idp','powershell','maxima','icon','coffeescript','fortran','octave','autohotkey','prolog','constraint handling rules','logtalk','awk','kotlin','dart','javascript','nemerle','erlang','php','autoit','r','bc']:
 2556            (Name),
 2557        ['julia']:
 2558            (Name,ws,"::",ws,Type),
 2559        ['rebol']:
 2560            (Type,ws,"[",ws,Name,ws,"]"),
 2561        ['openoffice basic','gambas','visual basic .net']:
 2562            (Name,ws_,"As",ws_,Type),
 2563        ['visual basic']:
 2564            (Name,ws_,"as",ws_,Type),
 2565        ['perl']:
 2566            (Name),
 2567        ['wolfram']:
 2568            (Name,"_"),
 2569        ['z3']:
 2570            ("(",ws,Name,ws_,Type,ws,")")
 2571        ]).
 2572
 2573main_method_(Data,[Body,Indent]) -->
 2574	langs_to_output(Data,main_method,[
 2575		['java']:
 2576			static_method_(Data, ["main",int,("String[] args"),Body,Indent])
 2577	]).
 2578
 2579
 2580
 2581enum_(Data,[Name,Body,Indent]) -->
 2582        langs_to_output(Data,enum,[
 2583        ['c']:
 2584                ("typedef",ws_,"enum",ws,"{",ws,Body,(Indent;ws),"}",ws,Name,ws,";"),
 2585        ['seed7']:
 2586                ("const",ws_,"type",ws,":",ws,Name,ws_,"is",ws_,"new",ws_,"enum",ws_,Body,(Indent;ws_),"end",ws_,"enum",ws,";"),
 2587        ['ada']:
 2588                ("type",ws_,Name,ws_,"is",ws_,"(",ws,Body,ws,")",ws,";"),
 2589        ['perl 6']:
 2590                ("enum",ws_,Name,ws_,"<",ws,Body,ws,">",ws,";"),
 2591        ['java']:
 2592                ("public",ws_,"enum",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}"),
 2593        ['c#','c++','typescript']:
 2594                ("enum",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}",ws,";"),
 2595        ['haxe','rust','swift','vala']:
 2596                ("enum",ws_,Name,ws,"{",ws,Body,(Indent;ws),"}"),
 2597        ['swift']:
 2598                ("enum",ws_,Name,ws,"{",ws,"case",ws_,Body,(Indent;ws),"}"),
 2599        ['fortran']:
 2600                ("ENUM",ws,"::",ws,Name,ws_,Body,(Indent;ws_),"END",ws_,"ENUM"),
 2601        ['go']:
 2602                ("type",ws_,Name,ws_,"int",ws_,"const",ws,"(",ws_,Body,ws_,")"),
 2603        ['scala']:
 2604                ("object",ws_,Name,ws_,"extends",ws_,"Enumeration",ws,"{",ws,"val",ws_,Body,ws,"=",ws,"Value",ws,"}")
 2605        ]).
 2606
 2607import_(Data,[A]) -->
 2608        langs_to_output(Data,import,[
 2609        ['r']:
 2610                ("source",ws,"(",ws,"\"",ws,A,ws,".",ws,"r\"",ws,")"),
 2611        ['javascript']:
 2612                ("import",ws_,"*",ws_,"as",ws_,A,ws_,"from",ws_,"'",ws,A,ws,"'",ws,";",!),
 2613        ['clojure']:
 2614                ("(",ws,"import",ws_,A,ws,")"),
 2615        ['monkey x']:
 2616                ("Import",ws_,A),
 2617        ['fortran']:
 2618                ("USE",ws_,A),
 2619        ['rebol']:
 2620                (A,ws,":",ws_,"load",ws_,"%",ws,A,ws,".r"),
 2621        ['prolog']:
 2622                (":-",ws,"consult(",ws,A,ws,")"),
 2623        ['minizinc']:
 2624                ("include",ws_,"'",ws,A,ws,".mzn'",ws,";"),
 2625        ['php']:
 2626                ("include",ws_,"'",ws,A,ws,".php'",ws,";"),
 2627        ['c','c++']:
 2628                ("#include",ws_,"\"",ws,A,ws,".h\""),
 2629        ['lua','ruby']:
 2630                ("require",ws_,"\"",ws,A,ws,"\""),
 2631        ['c#','vala']:
 2632                ("using",ws_,A,ws,";"),
 2633        ['julia']:
 2634                ("using",ws_,A),
 2635        ['haskell','purescript','engscript','scala','go','groovy','picat','elm','swift','monkey x']:
 2636                ("import",ws_,A),
 2637        :
 2638                ("import",ws_,A,ws,";"),
 2639        ['dart']:
 2640                ("import",ws_,"'",ws,A,ws,".dart'",ws,";"),
 2641        ['perl','perl 6','chapel']:
 2642                ("\"use",ws,A,ws,";\"")
 2643        ]).
 2644
 2645
 2646comment_(Data,[A]) -->
 2647	langs_to_output(Data,comment,[
 2648	['java','javascript','c','c#','c++','php','perl','swift']:
 2649		("//",A),
 2650	['cython','perl','octave','ruby']:
 2651		("#",A),
 2652	['lua','haskell','vhdl']:
 2653		("--",A),
 2654	['ocaml']:
 2655		("(*",A,"*)"),
 2656	['prolog','constraint handling rules','erlang','txl']:
 2657		("%",A),
 2658	['visual basic','visual basic .net']:
 2659		("'",A)
 2660    ]).
 2661
 2662first_case_(Data,[B,Compare_expr,Expr,Case_or_default]) -->
 2663    langs_to_output(Data,first_case,[
 2664    ['julia',octave]:
 2665            ("if",ws_,Compare_expr,ws_,"then",ws_,B,ws_,Case_or_default),
 2666    ['javascript','d','java','c#','c','c++','typescript','dart','php',hack]:
 2667			("case",ws_,Expr,ws,":",!,ws,B,ws,"break",ws,";",!,ws,Case_or_default),
 2668    [go,'haxe',swift]:
 2669            ("case",ws_,Expr,ws,":",ws,B,ws,Case_or_default),
 2670    ['fortran']:
 2671            ("CASE",ws,"(",ws,Expr,ws,")",ws_,B),
 2672    [rust]:
 2673            (Expr,ws,"=>",ws,"{",ws,B,ws,Case_or_default,(Indent;ws),"}"),
 2674    [haskell,'erlang','elixir',ocaml]:
 2675            (Expr,ws,"->",ws,B,ws,Case_or_default),
 2676    [clips]:
 2677            ("(",ws,"case",ws_,Expr,ws_,"then",ws_,B,ws,Case_or_default,ws,")"),
 2678    [scala]:
 2679            ("case",ws_,Expr,ws,"=>",ws,B,ws,Case_or_default),
 2680    [rebol]:
 2681            (Expr,ws,"[",ws,B,ws,Case_or_default,"]"),
 2682    [octave]:
 2683            ("case",ws_,Expr,ws_,B,ws,Case_or_default),
 2684    [clojure]:
 2685            ("(",ws,Expr,ws_,B,ws,Case_or_default,ws,")"),
 2686    [pascal,delphi]:
 2687            (Expr,ws,":",ws,B,ws,Case_or_default),
 2688    [chapel]:
 2689            ("when",ws_,Expr,ws,"{",ws,B,ws,Case_or_default,(Indent;ws),"}"),
 2690    [wolfram]:
 2691            (Expr,ws,",",ws,B,ws,Case_or_default)
 2692        ]).
 2693
 2694case(Data,[A,B,Expr,Case_or_default,Indent]) -->
 2695    langs_to_output(Data,case,[
 2696    ['julia',octave]:
 2697            ("elsif",ws_,A,ws_,"then",ws_,B,ws,Case_or_default),
 2698    ['javascript','d','java','c#','c','c++','typescript','dart','php','hack']:
 2699            ("case",ws_,Expr,ws,":",!,ws,B,ws,"break",ws,";",!,ws,Case_or_default),
 2700    [go,'haxe',swift]:
 2701            ("case",ws_,Expr,ws,":",ws,B,ws,Case_or_default),
 2702    ['fortran']:
 2703            ("CASE",ws,"(",ws,Expr,ws,")",ws_,B,ws,Case_or_default),
 2704    [rust]:
 2705            (Expr,ws,"=>",ws,"{",ws,B,(Indent;ws),"}",ws,Case_or_default),
 2706    [haskell,'erlang','elixir',ocaml]:
 2707            (Expr,ws,"->",ws,B,ws,Case_or_default),
 2708    [clips]:
 2709            ("(",ws,"case",ws_,Expr,ws_,"then",ws_,B,ws,")"),
 2710    [scala]:
 2711            ("case",ws_,Expr,ws,"=>",ws,B),
 2712    [rebol]:
 2713            (Expr,ws,"[",ws,B,ws,"]",ws,Case_or_default),
 2714    [octave]:
 2715            ("case",ws_,Expr,ws_,B,ws,Case_or_default),
 2716    [clojure]:
 2717            ("(",ws,Expr,ws_,B,ws,")",ws,Case_or_default),
 2718    [pascal,delphi]:
 2719            (Expr,ws,":",ws,B,ws,Case_or_default),
 2720    [chapel]:
 2721            ("when",ws_,Expr,ws,"{",ws,B,(Indent;ws),"}",ws,Case_or_default),
 2722    [wolfram]:
 2723            (Expr,ws,",",ws,B)
 2724    ]).
 2725
 2726
 2727default(Data,[A,Indent]) -->
 2728        langs_to_output(Data,default,[
 2729        ['fortran']:
 2730            ("CASE",ws_,"DEFAULT",ws_,A),
 2731        ['javascript','d','c','java','c#','c++','typescript','dart','php','haxe','hack','go','swift']:
 2732            ("default",ws,":",!,ws,A),
 2733        ['pascal','delphi']:
 2734            ("else",ws_,A),
 2735        ['haskell','erlang','ocaml']:
 2736            ("_",ws,"->",ws_,A),
 2737        ['rust']:
 2738            ("_",ws,"=>",ws,A),
 2739        ['clips']:
 2740            ("(",ws,"default",ws_,A,ws,")"),
 2741        ['scala']:
 2742            ("case",ws_,ws,"=>",ws,A),
 2743        ['rebol']:
 2744            ("][",A),
 2745        ['octave']:
 2746            ("otherwise",ws_,A),
 2747        ['chapel']:
 2748            ("otherwise",ws,"{",ws,A,(Indent;ws),"}"),
 2749        ['clojure']:
 2750            (A),
 2751        ['wolfram']:
 2752            ("_",ws,",",ws,A)
 2753        ]).
 2754
 2755
 2756elif(Data,[Indent,A,B]) -->
 2757        langs_to_output(Data,elif,[
 2758        ['sympy']:
 2759			("(",ws,B,ws,",",ws,A,ws,")"),
 2760        ['d','e','mathematical notation','chapel','pawn','ceylon','scala','typescript','autohotkey','awk','r','groovy','gosu','katahdin','java','swift','nemerle','c','dart','vala','javascript','c#','c++','haxe']:
 2761            ("else",ws_,"if",ws,"(",!,ws,A,ws,")",!,ws,"{",!,ws,B,(Indent;ws),"}"),
 2762        ['rust','go','englishscript']:
 2763            ("else",ws_,"if",ws_,A,ws,"{",!,ws,B,(Indent;ws),"}"),
 2764        ['php','hack','perl']:
 2765            ("elseif",ws,"(",ws,A,ws,")",ws,"{",!,ws,B,(Indent;ws),"}"),
 2766        ['julia','octave']:
 2767            ("elseif",ws_,A,ws_,B),
 2768        ['ruby','seed7','vhdl']:
 2769			("elsif",ws_,A,ws_,"then",ws_,B),
 2770		['lua','picat']:
 2771			("elseif",ws_,A,ws_,"then",ws_,B),
 2772        ['monkey x','visual basic','visual basic .net']:
 2773            ("ElseIf",ws_,A,ws_,B),
 2774        ['perl 6']:
 2775            ("elsif",ws_,A,ws_,"{",ws,B,(Indent;ws),"}"),
 2776        ['picat']:
 2777            ("elseif",ws_,A,ws_,"then",ws_,B),
 2778        ['prolog','logtalk','erlang','constraint handling rules']:
 2779            (A,ws,"->",ws,B),
 2780        ['r','f#']:
 2781            (A,ws,"<-",ws,B),
 2782        ['minizinc','ocaml','haskell','pascal','maxima','delphi','f#','livecode']:
 2783            ("else",ws_,"if",ws_,A,ws_,"then",ws_,B),
 2784        ['cython','python']:
 2785            ("elif",(python_ws_,A;python_ws,"(",python_ws,A,python_ws,")"),python_ws,":",python_ws,B),
 2786        ['fortran']:
 2787            ("ELSE",ws_,"IF",ws_,A,ws_,"THEN",ws_,B),
 2788        ['rebol']:
 2789            (A,ws,"[",ws,B,ws,"]"),
 2790        ['common lisp']:
 2791            ("(",ws,A,ws_,B,ws,")"),
 2792        ['wolfram']:
 2793            ("If",ws,"[",ws,A,ws,",",ws,B,ws,",",ws,C,(Indent;ws),"]"),
 2794        ['polish notation']:
 2795            ("elif",ws_,A,ws_,B),
 2796        ['reverse polish notation']:
 2797            (A,ws_,B,ws_,C,ws_,"elif"),
 2798        ['clojure']:
 2799            (A,ws_,B,ws_,C)
 2800        ]),!.
 2801
 2802default_parameter_(Data,[Type,Name,Value]) -->
 2803        langs_to_output(Data,default_parameter,[
 2804        ['autohotkey','julia','nemerle','php','javascript']:
 2805            (Name,python_ws,"=",python_ws,Value),
 2806        ['c#','d','groovy','c++']:
 2807            (Type,ws_,Name,ws,"=",ws,Value),
 2808        ['dart']:
 2809            ("[",ws,Type,ws_,Name,ws,"=",ws,Value,ws,"]"),
 2810        ['scala','swift']:
 2811            (Name,python_ws,":",python_ws,Type,python_ws,"=",python_ws,Value),
 2812        ['haxe']:
 2813            ("?",ws,Name,ws,"=",ws,Value)
 2814        ]),!.
 2815
 2816%generate a random integer from Min (inclusive) to Max (exclusive)
 2817random_int_in_range(Data,[Min,Max]) -->
 2818	langs_to_output(Data,random_int_in_range,[
 2819		['python']:
 2820			("randrange",python_ws,"(",python_ws,Min,python_ws,",",python_ws,Max,python_ws,")"),
 2821		['javascript']:
 2822			("(",ws,"Math",ws,".",ws,"floor",ws,"(",ws,"Math",ws,".",ws,"random",ws,"(",ws,")",ws,"*",ws,"(",ws,Max,ws,"-",ws,Min,ws,"+",ws,"1",ws,")",ws,"+",ws,Min,ws,")"),
 2823		['php']:
 2824			("rand",ws,"(",ws,Min,ws,",",ws,Max,ws,"-",ws,"1",ws,")")
 2825	]),!.
 2826
 2827%generate a random integer from Min (inclusive) to Max (inclusive)
 2828random_int_in_inclusive_range(Data,[Min,Max]) -->
 2829	langs_to_output(Data,random_int_in_inclusive_range,[
 2830		['php']:
 2831			("rand",ws,"(",ws,Min,ws,",",ws,Max,ws,")")
 2832	]).
 2833
 2834%see https://www.rosettacode.org/wiki/Pick_random_element
 2835random_from_list(Data,[Arr]) -->
 2836	langs_to_output(Data,random_from_list,[
 2837		['python']:
 2838			("random",python_ws,".",python_ws,"choice",python_ws,"(",python_ws,Arr,python_ws,")"),
 2839		['php']:
 2840			("array_rand",ws,"(",ws,Arr,ws,")"),
 2841		['julia']:
 2842			("rand",ws,"(",ws,Arr,ws,")"),
 2843		['wolfram']:
 2844			("RandomChoice",ws,"[",ws,Arr,ws,"]"),
 2845		['ruby']:
 2846			(Arr,ws,".",ws,"sample"),
 2847		['perl 6']:
 2848			(Arr,ws,".",ws,"pick"),
 2849		['javascript','coffeescript']:
 2850			(Arr,python_ws,"[Math.floor(Math.random()*",python_ws,Arr,python_ws,".length)]"),
 2851		['perl']:
 2852			("$",ws,Arr,ws,"[",ws,"rand",ws,"@",ws,Arr,ws,"]"),
 2853		['clojure']:
 2854			("(",ws,"rand-nth",ws_,Arr,ws,")"),
 2855		['d']:
 2856			(Arr,ws,"[uniform(0,$)]")
 2857	]).
 2858
 2859random_number(Data) -->
 2860	langs_to_output(Data,random_number,[
 2861		['javascript','java','typescript','haxe']:
 2862			("Math",ws,".",ws,"random",ws,"(",ws,")"),
 2863		['python']:
 2864			("random",python_ws,".",python_ws,"random",python_ws,"(",python_ws,")"),
 2865		['php']:
 2866			("lcg_value",ws,"(",ws,")"),
 2867		['perl','ruby']:
 2868			("rand",ws,"(",ws,")")
 2869		
 2870	]),!.
 2871
 2872type(Data,auto_type) -->
 2873        langs_to_output(Data,auto_type,[
 2874        ['c++']:
 2875                "auto",
 2876        ['c']:
 2877                "__auto_type",
 2878        ['java','gnu smalltalk']:
 2879                "Object",
 2880        ['c#']:
 2881                "object",
 2882        ['pseudocode']:
 2883                ("object";"Object";"__auto_type";"auto")
 2884        ]).
 2885
 2886type(Data,regex) -->
 2887        langs_to_output(Data,regex,[
 2888        ['javascript']:
 2889                "RegExp",
 2890        ['c#','scala']:
 2891                "Regex",
 2892        ['c++']:
 2893                "regex",
 2894        ['cython','python']:
 2895                "retype",    
 2896        ['java']:
 2897                "Pattern",
 2898        ['haxe']:
 2899                "EReg",
 2900        ['pseudocode']:
 2901                ("EReg";"Pattern";"RegExp";"regex";"Regex")
 2902        ]).
 2903
 2904type(Data,[dict,Type_in_dict]) -->
 2905        langs_to_output(Data,dict,[
 2906        ['cython']:
 2907                "dict",
 2908        ['javascript','java']:
 2909                "Object",
 2910        ['c']:
 2911            "__auto_type",
 2912        ['c++']:
 2913            "map<string,",type(Data,Type_in_dict),">",
 2914        ['haxe']:
 2915            "map<String,",type(Data,Type_in_dict),">",
 2916        ['pseudocode']:
 2917            ("map<string,",type(Data,Type_in_dict),">";"dict")
 2918        ]).
 2919
 2920type(Data,int) -->
 2921        langs_to_output(Data,int,[
 2922        ['hack','python','systemverilog','transact-sql','dafny','janus','chapel','minizinc','engscript','cython','algol 68','d','octave','tcl','ml','awk','julia','gosu','ocaml','f#','pike','objective-c','go','cobra','dart','groovy','hy','java','c#','c','c++','vala','nemerle']:
 2923                "int",
 2924        ['php','vhdl','prolog','constraint handling rules','common lisp','picat']:
 2925                "integer",
 2926        ['fortran']:
 2927                "INTEGER",
 2928        ['rebol']:
 2929                "integer!",
 2930        ['ceylon','cosmos','gambas','openoffice basic','pascal','erlang','delphi','visual basic','visual basic .net']:
 2931                "Integer",
 2932        ['haxe','ooc','swift','scala','perl 6','z3','monkey x']:
 2933                "Int",
 2934        ['javascript','typescript','coffeescript','perl']:
 2935                "number",
 2936        ['haskell']:
 2937                "Num",
 2938        ['ruby']:
 2939                "fixnum"
 2940        ]).
 2941
 2942type(Data,string) -->
 2943    langs_to_output(Data,string,[
 2944    ['z3','ruby','cosmos','visual basic .net','java','ceylon','gambas','dart','gosu','groovy','scala','pascal','swift','haxe','haskell','visual basic','monkey x']:
 2945            "String",
 2946    ['vala','systemverilog','seed7','octave','picat','mathematical notation','polish notation','reverse polish notation','prolog','constraint handling rules','d','chapel','minizinc','genie','hack','nim','algol 68','typescript','coffeescript','octave','tcl','awk','julia','c#','f#','perl','javascript','go','php','c++','nemerle','erlang']:
 2947            "string",
 2948    ['c']:
 2949            "char*",
 2950    ['rebol']:
 2951            "string!",
 2952    ['fortran']:
 2953            "CHARACTER","(","LEN","=","*",")",
 2954    ['hy','python']:
 2955            "str",
 2956    ['pseudocode']:
 2957            ("str";"string";"String";"char*";"string!")
 2958    ]).
 2959
 2960type(Data,char) -->
 2961    langs_to_output(Data,char,[
 2962		['java','c','c#','c++']:
 2963			"char",
 2964		['javascript']:
 2965			"String"
 2966    ]).
 2967
 2968type(Data, bool) -->
 2969    langs_to_output(Data,bool,[
 2970    ['typescript','vhdl','seed7','hy','python','java','javascript','perl']:
 2971            "boolean",
 2972    ['c++','nim','octave','dafny','chapel','c','rust','minizinc','engscript','dart','d','vala','go','cobra','c#','f#','php','hack']:
 2973            "bool",
 2974    ['haxe','haskell','swift','julia','perl 6','z3','z3py','monkey x']:
 2975            "Bool",
 2976    ['fortran']:
 2977            "LOGICAL",
 2978    ['visual basic','visual basic .net','openoffice basic','ceylon','delphi','pascal','scala']:
 2979            "Boolean",
 2980    ['rebol']:
 2981            "logic!",
 2982    ['pseudocode']:
 2983            ("bool";"logic!";"Boolean";"boolean";"Bool";"LOGICAL")
 2984    ]).
 2985
 2986type(Data,void) -->
 2987    langs_to_output(Data,void,[
 2988    ['engscript','thrift','seed7','php','hy','cython','go','pike','objective-c','java','c','c++','c#','vala','typescript','d','javascript','dart']:
 2989            "void",
 2990    ['haxe','swift']:
 2991            "Void",
 2992    ['scala']:
 2993            "Unit",
 2994    ['pseudocode']:
 2995            ("Void","void","Unit")
 2996    ]).
 2997
 2998type(Data,double) -->
 2999        langs_to_output(Data,double,[
 3000        ['java','c','c#','c++','dart','vala']:
 3001                "double",
 3002        ['go']:
 3003                "float64",
 3004        ['haxe']:
 3005                "Float",
 3006        ['javascript']:
 3007                "number",
 3008        ['minizinc','php','python']:
 3009                "float",
 3010        ['swift']:
 3011                "Double",
 3012        ['haskell']:
 3013                "Num",
 3014        ['rebol']:
 3015                "decimal!",
 3016        ['fortran']:
 3017                ("double",ws_,"precision"),
 3018        ['z3','z3py']:
 3019                "Real",
 3020        ['octave']:
 3021                "scalar",
 3022        ['pseudocode']:
 3023                ("double","real","decimal","Num","float","Float","Real","float64","number")
 3024        ]).
 3025
 3026% https://rosettacode.org/wiki/Arrays
 3027type(Data,[array,Type]) -->
 3028    {ground(Type)}, %Type contains no unknown variables
 3029    langs_to_output(Data,array,[
 3030    ['java','c','c++','c#','typescript']:
 3031            (type(Data,Type),"[]"),
 3032    ['go']:
 3033            ("[]", type(Data,Type)),
 3034    ['cython','python']:
 3035            "list",
 3036    ['haxe','swift']:
 3037			("Array<",type(Data,Type),">"),
 3038    ['visual basic .net']:
 3039            (type(Data,Type),"()"),
 3040    ['javascript','cosmos']:
 3041            "Array"
 3042    ]).
 3043
 3044concatenate_string_to_int_(Data,[A,B]) -->
 3045	langs_to_output(Data,conatenate_string_to_int,[
 3046	['java','javascript','perl','c#','julia','lua']:
 3047		concatenate_string_(Data,[A,B]),
 3048	['python_temp','ruby','c++','swift','php']:
 3049		concatenate_string_(Data,[A,type_conversion_(Data,[int,string,B])])
 3050    ]).
 3051
 3052concatenate_int_to_string_(Data,[A,B]) -->
 3053	langs_to_output(Data,conatenate_int_to_string,[
 3054	['java','javascript','perl','c#','julia','lua']:
 3055		concatenate_string_(Data,[A,B]),
 3056	['python_temp','ruby','c++','swift','php']:
 3057		concatenate_string_(Data,[type_conversion_(Data,[int,string,A]),B])
 3058    ]).
 3059
 3060grammar_statement_(Data,[Name,Body]) -->
 3061	langs_to_output(Data,grammar_statement,[
 3062	['pegjs']:
 3063		(Name,ws,"=",ws,Body)
 3064    ]).
 3065
 3066grammars(['marpa','abnf','waxeye','nearley','antlr','peg.js','definite clause grammars','parslet','lpeg','ometa','parboiled','wirth syntax notation']).
 3067
 3068statement_separator(Data) -->
 3069    {offside_rule_langs(Offside_rule_langs)},langs_to_output(Data,statement_separator,[
 3070    ['marpa','abnf','wirth syntax notation','parboiled','waxeye','nearley','antlr','peg.js','definite clause grammars','parslet']:
 3071			ws_,
 3072    ['pydatalog','pddl','visual basic .net','lua','ruby','hy','pegjs','racket','vbscript','monkey x','livecode','polish notation','reverse polish notation','clojure','clips','common lisp','emacs lisp','scheme','dafny','z3','elm','bash','mathematical notation','katahdin','frink','minizinc','aldor','cobol','ooc','genie','eclipse','nools','agda','pl/i','rexx','idp','falcon','processing','sympy','maxima','pyke','elixir','gnu smalltalk','seed7','standard ml','occam','boo','drools','icon','mercury','engscript','pike','oz','kotlin','pawn','freebasic','ada','powershell','gosu','nim','cython','openoffice basic','algol 68','d','ceylon','rust','coffeescript','fortran','octave','ml','autohotkey','delphi','pascal','f#','self','swift','nemerle','autoit','cobra','julia','groovy','scala','ocaml','gambas','matlab','rebol','red','go','awk','haskell','r','visual basic']:
 3073            ws_,
 3074    Offside_rule_langs:
 3075			"",
 3076    ['java','vhdl','c','pseudocode','perl 6','haxe','javascript','c++','c#','php','dart','actionscript','typescript','processing','vala','bc','ceylon','hack','perl']:
 3077            ws,
 3078    ['wolfram']:
 3079            ";",
 3080    ['picat','lpeg','prolog','constraint handling rules','logtalk','erlang','lpeg']:
 3081            ",",
 3082    ['gnu smalltalk']:
 3083            (".",ws_)
 3084    ]).
 3085
 3086initializer_list_separator(Data) -->
 3087    langs_to_output(Data,initializer_list_separator,[
 3088    ['ruby','r','constraint handling rules','english','lua','cython','python','visual basic .net','cosmos','erlang','nim','seed7','vala','polish notation','reverse polish notation','d','frink','fortran','chapel','octave','julia','pseudocode','pascal','delphi','prolog','minizinc','engscript','cython','groovy','dart','typescript','coffeescript','nemerle','javascript','haxe','haskell','rebol','polish notation','swift','java','picat','c#','go','c++','c','visual basic','php','scala','perl','wolfram']:
 3089            ",",
 3090    ['rebol']:
 3091            ws_,
 3092    ['ocaml']:
 3093			%this is the separator for arrays and lists in OCaml
 3094            ";",
 3095    ['pseudocode']:
 3096            (",";";")
 3097    ]).
 3098
 3099key_value_separator(Data) -->
 3100    langs_to_output(Data,key_value_separator,[
 3101    ['python','english_temp','cosmos','lua','prolog','picat','go','dart','d','c#','frink','swift','javascript','typescript','php','perl','julia','haxe','c++','scala','octave','elixir','wolfram']:
 3102            ",",
 3103    ['pseudocode']:
 3104            (",";";"),
 3105    ['rebol','gnu smalltalk']:
 3106            ws_
 3107    ]).
 3108
 3109
 3110enum_list_(Data,[A]) -->
 3111			langs_to_output(Data,enum_list_,[
 3112			['java','seed7','vala','perl 6','swift','c++','c#','haxe','fortran','typescript','c','ada','scala']:
 3113					(A),
 3114			['go']:
 3115					(A,ws,"=",ws,"iota")
 3116			]).
 3117
 3118top_level_statement_(Data,A) -->
 3119    {Data = [Lang|_]},
 3120    ({memberchk(Lang,['prolog','erlang','picat','logtalk','constraint handling rules'])}->
 3121        A,".";
 3122    {memberchk(Lang,['minizinc'])}->
 3123        A,";";
 3124    A).
 3125% see rosettacode.org/wiki/Regular_expressions
 3126regex_literal_(Data,[S]) -->
 3127    langs_to_output(Data,regex_literal,[
 3128    ['javascript']:
 3129        ("/",S,"/"),
 3130    ['haxe']:
 3131        ("~/",S,"/"),
 3132    ['java']:
 3133        ("Pattern",ws,".",ws,"compile",ws,"(\"",S,"\")"),
 3134    ['c++']:
 3135        ("regex::regex",ws,"(\"",S,"\")"),
 3136    ['scala','c#']:
 3137        ("new",ws,"Regex",ws,"(\"",S,"\")")
 3138    ]).
 3139
 3140include_in_each_file(Data) -->
 3141    langs_to_output(Data,include_in_each_file,[
 3142    ['c']:
 3143		"#include<stdio.h>\n#include<math.h>",
 3144    ['prolog','constraint handling rules']:
 3145        (":- initialization(main).\n:- set_prolog_flag(double_quotes, chars).\n:- use_module(library(clpfd)).\n:- use_module(library(func))."),
 3146    ['perl']:
 3147        "use strict;\nuse warnings;",
 3148	['haxe']:
 3149		"using StringTools;",
 3150	['java']:
 3151		"import java.util.ArrayList;\nimport java.util.Collections;",
 3152	['python']:
 3153		"",
 3154	['sympy']:
 3155		"from sympy import *"
 3156    ]),"\n";"".
 3157
 3158% spelled backwards
 3159% reverse a string (not in-place)
 3160% see https://www.rosettacode.org/wiki/Reverse_a_string
 3161reverse_string_(Data,[Str]) -->
 3162        langs_to_output(Data,reverse_string,[
 3163        ['java']:
 3164                ("new",ws_,"StringBuilder",ws,"(",ws,Str,ws,")",ws,".",ws,"reverse",ws,"(",ws,")",ws,".",ws,"toString",ws,"(",ws,")"),
 3165        %this one has been verified to work correctly
 3166        %see http://perldoc.perl.org/functions/reverse.html
 3167        ['perl']:
 3168                ("(",ws,"scalar",ws_,"reverse",ws,"(",Str,")",ws,")"),
 3169        ['php']:
 3170                ("strrev",ws,"(",ws,Str,ws,")"),
 3171        ['english']:
 3172				("(",Str,python_ws_,("spelled";"written"),python_ws_,("backwards";"backward"),")"),
 3173        ['javascript']:
 3174                ("esrever",ws,".",ws,"reverse",ws,"(",ws,Str,ws,")"),
 3175        ['common lisp','haskell']:
 3176				("(",ws,"reverse",ws_,Str,ws,")"),
 3177		%the next one still doesn't work correctly with this parser
 3178		['python_temp']:
 3179				(Str,"[::-1]")
 3180        ]).
 3181
 3182key_value_(Data,[A,B]) -->
 3183        langs_to_output(Data,key_value,[
 3184        ['groovy','english_temp','d','dart','javascript','typescript','coffeescript','swift','elixir','swift','go']:
 3185                (A,ws,":",!,ws,B),
 3186        ['python']:
 3187                ("\"",python_ws,A,python_ws,"\"",python_ws,":",python_ws,B),
 3188        ['php','haxe','perl','ruby','julia']:
 3189                (A,ws,"=>",ws,B),
 3190        ['rebol']:
 3191                (A,ws_,B),
 3192        ['picat','lua']:
 3193                (A,ws,"=",ws,B),
 3194        ['c++','c#']:
 3195                ("{",ws,("\"",ws,A,ws,"\""),ws,",",ws,B,ws,"}"),
 3196        ['scala','wolfram','gnu smalltalk']:
 3197                (A,ws,"->",ws,B),
 3198        ['octave','cosmos']:
 3199                (A,ws,",",ws,B),
 3200        ['frink']:
 3201                ("[",ws,A,ws,",",ws,B,ws,"]"),
 3202        ['prolog']:
 3203                (A,ws,"-",ws,B)
 3204        ]).
 3205
 3206array_slice_(Data,[A,B,C]) -->
 3207        langs_to_output(Data,array_slice,[
 3208            ['cython']:
 3209                (A,python_ws,"[",python_ws,B,python_ws,":",python_ws,C,python_ws,"]")
 3210        ]).
 3211
 3212compare_(Data,string,[A,B]) -->
 3213    langs_to_output(Data,compare_string,[
 3214    ['r']:
 3215            ("identical",ws,"(",ws,A,ws,",",ws,B,ws,")"),
 3216    ['emacs lisp']:
 3217            ("(",ws,"string=",ws_,A,ws_,B,ws,")"),
 3218    ['clojure']:
 3219            ("(",ws,"=",ws_,A,ws_,B,ws,")"),
 3220    ['visual basic','delphi','vbscript','f#','prolog','mathematical notation','ocaml','livecode','monkey x']:
 3221            (A,ws,"=",ws,B),
 3222    ['pydatalog','ruby','lua','perl 6','python','cython','englishscript','chapel','julia','fortran','minizinc','picat','go','vala','autoit','rebol','ceylon','groovy','scala','coffeescript','awk','haskell','haxe','dart','swift']:
 3223            (A,python_ws,"==",python_ws,B),
 3224    ['javascript','php','typescript','hack']:
 3225            (A,ws,"===",ws,B),
 3226    ['english']:
 3227            (A,ws,synonym("="),ws,B),
 3228    ['c','octave']:
 3229            ("strcmp",ws,"(",ws,A,ws,",",ws,B,ws,")",ws,"==",ws,"0"),
 3230    ['c++','systemverilog']:
 3231            (A,ws,".",ws,"compare",ws,"(",ws,B,ws,")"),
 3232    ['c#']:
 3233            (A,ws,".",ws,"Equals",ws,"(",ws,B,ws,")"),
 3234    ['java']:
 3235            (A,ws,".",ws,"equals",ws,"(",ws,B,ws,")"),
 3236    ['common lisp']:
 3237            ("(",ws,"equal",ws_,A,ws_,B,ws,")"),
 3238    ['clips']:
 3239            ("(",ws,"str-compare",ws_,A,ws_,B,ws,")"),
 3240    ['hy']:
 3241            ("(",ws,"=",ws_,A,ws_,B,ws,")"),
 3242    ['perl']:
 3243            (A,ws_,"eq",ws_,B),
 3244    ['erlang']:
 3245            ("string",ws,":",ws,"equal",ws,"(",ws,A,ws,",",ws,B,ws,")"),
 3246    ['polish notation']:
 3247            ("=",ws_,A,ws_,B),
 3248    ['reverse polish notation']:
 3249            (A,ws_,B,ws_,"=")
 3250    ]).
 3251
 3252compare_(Data,bool,[Exp1,Exp2]) -->
 3253        langs_to_output(Data,compare_bool,[
 3254        ['nim','z3py','pydatalog','e','ceylon','cython','perl 6','englishscript','cython','mathematical notation','dafny','wolfram','d','rust','r','minizinc','frink','picat','pike','pawn','processing','c++','ceylon','coffeescript','octave','swift','awk','julia','perl','groovy','erlang','haxe','scala','java','vala','dart','c#','c','go','haskell']:
 3255                (Exp1,("=="),Exp2),
 3256        ['javascript','php']:
 3257                (Exp1,("===";"=="),Exp2),
 3258        ['prolog']:
 3259                (Exp1,"=",Exp2)
 3260        ]).
 3261
 3262compare_(Data,int,[Var1,Var2]) -->
 3263        langs_to_output(Data,compare_int,[
 3264        ['r']:
 3265                ("identical",ws,"(",ws,Var1,ws,",",ws,Var2,ws,")"),
 3266        ['sympy']:
 3267                ("Eq",ws,"(",ws,Var1,ws,",",ws,Var2,ws,")"),
 3268        ['nim','cython','lua','python','z3py','pydatalog','e','ceylon','perl 6','englishscript','cython','mathematical notation','dafny','wolfram','d','rust','r','minizinc','frink','picat','pike','pawn','processing','c++','ceylon','coffeescript','octave','swift','awk','julia','perl','groovy','erlang','haxe','scala','java','vala','dart','c#','c','go','haskell']:
 3269                (Var1,python_ws,"==",python_ws,Var2),
 3270        ['english']:
 3271                (Var1,python_ws,synonym("="),python_ws,Var2),
 3272        ['javascript','php','typescript','hack']:
 3273                (Var1,ws,"===",ws,Var2),
 3274        ['z3','emacs lisp','common lisp','clips','racket']:
 3275                ("(",ws,"=",ws_,Var1,ws_,Var2,ws,")"),
 3276        ['fortran']:
 3277                (Var1,ws,".eq.",ws,Var2),
 3278        ['maxima','seed7','monkey x','gap','rebol','f#','autoit','pascal','delphi','visual basic','ocaml','livecode','vbscript']:
 3279                (Var1,ws,"=",ws,Var2),
 3280        ['prolog']:
 3281                (Var1,ws,("#=","=";"=:="),ws,Var2),
 3282        ['clojure']:
 3283                ("(",ws,"=",ws_,Var1,ws_,Var2,ws,")"),
 3284        ['reverse polish notation']:
 3285                (Var1,ws_,Var2,ws_,"="),
 3286        ['polish notation']:
 3287                ("=",ws_,Var1,ws_,Var2)
 3288        ]).
 3289
 3290less_than_(Data,[A,B]) -->
 3291		{prefix_arithmetic_langs(Prefix_arithmetic_langs),infix_arithmetic_langs(Infix_arithmetic_langs)},
 3292        langs_to_output(Data,less_than,[
 3293		Infix_arithmetic_langs:
 3294                (infix_operator("<",A,B)),
 3295        ['english']:
 3296                (
 3297					infix_operator("<",A,B);
 3298					A,python_ws_,"is",python_ws_,synonym("less"),python_ws_,"than",python_ws_,B
 3299				),
 3300        Prefix_arithmetic_langs:
 3301                ("(",ws,"<",ws_,A,ws_,B,ws,")")
 3302        ]).
 3303
 3304%alphabetical string comparison
 3305string_less_than_(Data,[A,B]) -->
 3306        langs_to_output(Data,less_than,[
 3307		['c++','python']:
 3308                (infix_operator("<",A,B))
 3309        ]).
 3310
 3311%alphabetical string comparison
 3312string_greater_than_(Data,[A,B]) -->
 3313        langs_to_output(Data,less_than,[
 3314		['c++','python']:
 3315                (infix_operator(">",A,B))
 3316        ]).
 3317
 3318less_than_or_equal_to_(Data,[A,B]) -->
 3319		{prefix_arithmetic_langs(Prefix_arithmetic_langs),infix_arithmetic_langs(Infix_arithmetic_langs)},
 3320        langs_to_output(Data,less_than_or_equal,[
 3321        ['pascal','sympy','vhdl','python','elixir','visual basic .net','lua','ruby','scriptol','z3py','ats','pydatalog','e','vbscript','livecode','monkey x','perl 6','englishscript','cython','gap','mathematical notation','wolfram','chapel','katahdin','frink','minizinc','picat','java','eclipse','d','ooc','genie','janus','pl/i','idp','processing','maxima','seed7','self','gnu smalltalk','drools','standard ml','oz','cobra','pike','engscript','kotlin','pawn','freebasic','matlab','ada','freebasic','gosu','gambas','nim','autoit','algol 68','ceylon','groovy','rust','coffeescript','typescript','fortran','octave','ml','hack','autohotkey','scala','delphi','tcl','swift','vala','c','f#','c++','dart','javascript','rebol','julia','erlang','ocaml','c#','nemerle','awk','java','perl','haxe','php','haskell','go','r','bc','visual basic']:
 3322                infix_operator("<=",A,B),
 3323        ['prolog']:
 3324            (A,ws,("#=<";"=<"),ws,B),
 3325        ['english']:
 3326			(
 3327				A,python_ws_,("is",python_ws_,synonym("less"),python_ws_,"than",python_ws_,"or",python_ws_,"equal",python_ws_,"to";
 3328				"is",python_ws_,"not",python_ws_,synonym("more"),python_ws_,"than"),python_ws_,B
 3329			),
 3330        Prefix_arithmetic_langs:
 3331				("(",ws,"<=",ws_,A,ws_,B,")")
 3332        ]).
 3333
 3334greater_than_or_equal_to_(Data,[A,B]) -->
 3335		{prefix_arithmetic_langs(Prefix_arithmetic_langs),infix_arithmetic_langs(Infix_arithmetic_langs)},
 3336        langs_to_output(Data,'greater_than_or_equal',[
 3337        ['pascal','sympy','vhdl','elixir','visual basic .net','python','lua','ruby','scriptol','z3py','ats','pydatalog','e','vbscript','livecode','monkey x','perl 6','englishscript','cython','gap','mathematical notation','wolfram','chapel','katahdin','frink','minizinc','picat','java','eclipse','d','ooc','genie','janus','pl/i','idp','processing','maxima','seed7','self','gnu smalltalk','drools','standard ml','oz','cobra','pike','engscript','kotlin','pawn','freebasic','matlab','ada','freebasic','gosu','gambas','nim','autoit','algol 68','ceylon','groovy','rust','coffeescript','typescript','fortran','octave','ml','hack','autohotkey','scala','delphi','tcl','swift','vala','c','f#','c++','dart','javascript','rebol','julia','erlang','ocaml','c#','nemerle','awk','java','perl','haxe','php','haskell','go','r','bc','visual basic']:
 3338                (A,ws,">=",ws,B),
 3339        ['prolog']:
 3340                (A,ws,("#>=";">="),ws,B),
 3341        Prefix_arithmetic_langs:
 3342				("(",ws,">=",ws_,A,ws_,B,")")
 3343        ]).
 3344
 3345greater_than_(Data,[A,B]) -->
 3346		{prefix_arithmetic_langs(Prefix_arithmetic_langs),infix_arithmetic_langs(Infix_arithmetic_langs)},
 3347        langs_to_output(Data,'greater_than',[
 3348		Infix_arithmetic_langs:
 3349                (infix_operator(">",A,B)),
 3350        ['english']:
 3351                (
 3352					infix_operator(">",A,B);
 3353					A,python_ws_,"is",python_ws_,synonym("greater"),python_ws_,"than",python_ws_,B
 3354				),
 3355		Prefix_arithmetic_langs:
 3356                ("(",ws,">",ws_,A,ws_,B,ws,")")
 3357        ]).
 3358
 3359universal_quantification_(Data,Variable,Array,Compare_each_to,[English_expr,Output_Expr]) -->
 3360		{Data=[Lang|_],prefix_arithmetic_langs(Prefix_arithmetic_langs),infix_arithmetic_langs(Infix_arithmetic_langs)},
 3361		({Lang='english'}->
 3362			(Array,python_ws_,"are",python_ws_,English_expr,python_ws_,Compare_each_to);
 3363		({unique_var(Variable)},all_true_(Data,[Variable,Array,Output_Expr]))).
 3364
 3365coordinating_conjunction_(Data,int,[Variable,Compare_each_to,Outputs]) :-
 3366	Outputs=[("not",python_ws_,"equal",python_ws_,"to"),
 3367			int_not_equal_(Data,[Variable,Compare_each_to])].
 3368
 3369coordinating_conjunction_(Data,int,[Variable,Compare_each_to,Outputs]) :-
 3370	Outputs=[("equal",python_ws_,"to"),
 3371			compare_int_(Data,[Variable,Compare_each_to])].
 3372
 3373coordinating_conjunction_(Data,int,[Variable,Compare_each_to,Outputs]) :-
 3374	Outputs=[("less",python_ws_,"than"),
 3375			less_than_(Data,[Variable,Compare_each_to])].
 3376	
 3377coordinating_conjunction_(Data,int,[Variable,Compare_each_to,Outputs]) :-
 3378	Outputs=[(synonym("greater"),python_ws_,"than"),
 3379			greater_than_(Data,[Variable,Compare_each_to])].
 3380
 3381coordinating_conjunction(Data,Conjunction,int,[Variable,[Compare_each_to]]) -->
 3382	{coordinating_conjunction_(Data,int,[Variable,parentheses_expr(Data,int,Compare_each_to),[English_expr,Output_expr]])},
 3383	({Data=['english'|_]}->
 3384		English_expr,python_ws_,parentheses_expr(Data,int,Compare_each_to));
 3385	greater_than_(Data,[Variable,parentheses_expr(Data,int,Compare_each_to)]).
 3386
 3387coordinating_conjunction(Data,'or',int,[Variable,[A|B]]) -->
 3388		coordinating_conjunction(Data,'or',int,[Variable,[A]])," or ",
 3389		coordinating_conjunction(Data,'or',int,[Variable,B]).
 3390
 3391coordinating_conjunction(Data,'and',int,[Variable,[A|B]]) -->
 3392		coordinating_conjunction(Data,'and',int,[Variable,[A]])," and ",
 3393		coordinating_conjunction(Data,'and',int,[Variable,B]).
 3394
 3395
 3396
 3397
 3398coordinating_conjunctions(Data,Conjunction,int,[Variable,Vars]) -->
 3399	{Data=['english'|_]} ->
 3400	Variable,python_ws_,"is",python_ws_,coordinating_conjunction(Data,Conjunction,int,[Variable,Vars]);
 3401	coordinating_conjunction(Data,Conjunction,int,[Variable,Vars]).
 3402
 3403universal_quantifications_(Data,int,[Array,Compare_each_to,English_expr]) -->
 3404	coordinating_conjunction_(Data,int,[Variable,Compare_each_to,[English_expr,Output_expr]]),
 3405	universal_quantification_(
 3406		Data,
 3407		Variable,
 3408		Array,
 3409		Compare_each_to,
 3410		[English_expr,Output_expr]
 3411	),{writeln('Translated with the universal_quantifications_ predicate')}.
 3412
 3413string_not_equal_(Data,[A,B]) -->
 3414	langs_to_output(Data,string_not_equal,[
 3415		['python']:
 3416			(infix_operator("!=",A,B)),
 3417		['javascript','php']:
 3418			(infix_operator("!==",A,B)),
 3419		['english']:
 3420				(A,python_ws_,synonym("does not equal"),python_ws_,B),
 3421		['java']:
 3422				("!",A,ws,".",ws,"equals",ws,"(",ws,B,ws,")"),
 3423		['perl']:
 3424				(A,ws_,"ne",ws_,B)
 3425	]).
 3426
 3427int_not_equal_(Data,[A,B]) -->
 3428        langs_to_output(Data,int_not_equal,[
 3429        ['english']:
 3430				(A,ws_,synonym("does not equal"),ws_,B),
 3431        ['javascript','php',elixir]:
 3432                (infix_operator(("!==";"!="),A,B)),
 3433        ['java','ruby','python','cosmos','nim','octave','r','picat','englishscript','perl 6','wolfram','c','c++','d','c#','julia','perl','haxe','cython','minizinc','scala','swift','go','rust','vala']:
 3434                (infix_operator("!=",A,B)),
 3435        ['rebol','scriptol','seed7','visual basic','visual basic .net','gap','ocaml','livecode','monkey x',vbscript,delphi]:
 3436                (infix_operator("<>",A,B)),
 3437        ['prolog']:
 3438                ("(",ws,A,ws,"#\\=",ws,B,ws,")";"dif",ws,"(",ws,A,ws,",",ws,B,ws,")"),
 3439        ['common lisp',z3]:
 3440                ("(",ws,"not",ws,"(",ws,"=",ws_,A,ws_,B,")",ws,")")
 3441        ]).
 3442
 3443pow_(Data,[A,B]) -->
 3444    langs_to_output(Data,pow,[
 3445    ['javascript','java','typescript','haxe','actionscript']:
 3446            ("Math",ws,".",ws,"pow",ws,"(",!,ws,A,ws,",",ws,B,ws,")"),
 3447    ['coffeescript']:
 3448			("Math",python_ws,".",python_ws,"pow",python_ws,"(",python_ws,A,python_ws,",",python_ws,B,python_ws,")"),
 3449    ['seed7','ruby','chapel','haskell','cobol','picat','ooc','pl/i','rexx','maxima','awk','r','f#','autohotkey','tcl','autoit','groovy','octave','perl','perl 6','fortran']:
 3450            (A,python_ws,"**",python_ws,B),
 3451	['python','cython']:
 3452            (
 3453				A,python_ws,"**",python_ws,B;
 3454				"math",python_ws,".",python_ws,"pow(",A,python_ws,",",B,python_ws,")"
 3455			),
 3456    ['english']:
 3457            (
 3458				A,python_ws,("**";"^"),python_ws,B;
 3459				A,python_ws_,"to",python_ws_,"the",python_ws,"power",python_ws_,"of",python_ws_,B
 3460			),
 3461    ['scala']:
 3462            ("scala.math.pow",ws,"(",ws,A,ws,",",ws,B,ws,")"),
 3463    ['c#']:
 3464            ("Math",ws,".",ws,"Pow",ws,"(",ws,A,ws,",",ws,B,ws,")"),
 3465    ['rebol']:
 3466            ("power",ws_,A,ws_,B),
 3467    ['c','c++','php','hack','swift','minizinc','dart','d']:
 3468            ("pow",ws,"(",ws,A,ws,",",ws,B,ws,")"),
 3469    ['julia','lua','engscript','visual basic','gambas','go','ceylon','wolfram','mathematical notation']:
 3470            (A,ws,"^",ws,B),
 3471    ['hy','common lisp','racket','clojure']:
 3472            ("(",ws,"expt",ws_,A,ws_,B,ws,")"),
 3473    ['erlang']:
 3474            ("math",ws,":",ws,"pow",ws,"(",ws,A,ws,",",ws,B,ws,")")
 3475    ]).
 3476
 3477sqrt(Data,[X]) -->
 3478        langs_to_output(Data,sqrt,[
 3479        ['livecode']:
 3480                ("(",ws,"the",ws_,"sqrt",ws_,"of",ws_,X,ws,")"),
 3481        ['java','javascript','typescript','haxe','ruby']:
 3482                ("Math",ws,".",ws,"sqrt",ws,"(",!,ws,X,ws,")"),
 3483        ['c#']:
 3484                ("Math",ws,".",ws,"Sqrt",ws,"(",ws,X,ws,")"),
 3485        ['c','seed7','julia','perl','php','perl 6','maxima','minizinc','prolog','octave','d','haskell','swift','mathematical notation','dart','picat']:
 3486                ("sqrt",ws,"(",ws,X,ws,")"),
 3487        ['rebol']:
 3488                ("square-root",ws_,X),
 3489        ['scala']:
 3490                ("scala",ws,".",ws,"math",ws,".",ws,"sqrt",ws,"(",ws,X,ws,")"),
 3491        ['c++']:
 3492                ("std",ws,"::",ws,"sqrt",ws,"(",ws,X,ws,")"),
 3493        ['erlang']:
 3494                ("math",ws,":",ws,"sqrt",ws,"(",ws,X,ws,")"),
 3495        ['wolfram']:
 3496                ("Sqrt",ws,"[",ws,X,ws,"]"),
 3497        ['common lisp','racket']:
 3498                ("(",ws,"sqrt",ws_,X,ws,")"),
 3499        ['fortran']:
 3500                ("SQRT",ws,"(",ws,X,ws,")"),
 3501        ['english_temp']:
 3502                ("(","square",python_ws_,"root",python_ws_,"of",python_ws_,X,")"),
 3503        ['go']:
 3504                ("math",ws,".",ws,"Sqrt",ws,"(",ws,X,ws,")")
 3505        ]).
 3506
 3507list_comprehension_(Data,[Variable,Array,Result,Condition]) -->
 3508        langs_to_output(Data,list_comprehension,[
 3509        ['cython','python']:
 3510                ("[",python_ws,Result,python_ws_,"for",python_ws_,Variable,python_ws_,"in",python_ws_,Array,python_ws_,"if",python_ws_,Condition,python_ws,"]"),
 3511        ['ceylon']:
 3512                ("{",ws,"for",ws,"(",ws,Variable,ws_,"in",ws_,Array,ws,")",ws_,"if",ws,"(",ws,Condition,ws,")",ws_,Result,ws,"}"),
 3513        ['javascript']:
 3514                ("[",ws,Result,ws_,"for",ws,"(",ws,Variable,ws_,"of",ws_,Array,ws,")",ws,"if",ws_,Condition,ws,"]"),
 3515        ['coffeescript']:
 3516                ("(",ws,Result,ws_,"for",ws_,Variable,ws_,"in",ws_,Array,ws_,"when",ws_,Condition,ws,")"),
 3517        ['minizinc']:
 3518                ("[",ws,Result,ws,"|",ws,Variable,ws_,"in",ws_,Array,ws_,"where",ws_,Condition,ws,"]"),
 3519        ['haxe']:
 3520                ("[",ws,"for",ws,"(",ws,Variable,ws_,"in",ws_,Array,ws,")",ws,"if",ws,"(",ws,Condition,ws,")",ws,Result,ws,"]"),
 3521        ['c#']:
 3522                ("(",ws,"from",ws_,Variable,ws_,"in",ws_,Array,ws_,"where",ws_,Condition,ws_,"select",ws_,Result,ws,")"),
 3523        ['haskell']:
 3524                ("[",ws,Result,ws,"|",ws,Variable,ws,"<-",ws,Array,ws,",",ws,Condition,ws,"]"),
 3525        ['erlang']:
 3526                ("[",ws,Result,ws,"||",ws,Variable,ws,"<-",ws,Array,ws,",",ws,Condition,ws,"]"),
 3527        ['scala']:
 3528                ("(",ws,"for",ws,"(",ws,Variable,ws,"<-",ws,Array,ws_,"if",ws_,Condition,ws,")",ws,"yield",ws_,Result,ws,")"),
 3529        ['groovy']:
 3530                ("array.grep",ws,"{",ws,Variable,ws,"->",ws,Condition,ws,"}.collect",ws,"{",ws,Variable,ws,"->",ws,Result,ws,"}"),
 3531        ['dart']:
 3532                (Array,ws,".",ws,"where",ws,"(",ws,Variable,ws,"=>",ws,Condition,ws,")",ws,".",ws,"map",ws,"(",ws,Variable,ws,"=>",ws,Result,ws,")"),
 3533        ['picat']:
 3534                ("[",ws,Result,ws,":",ws,Variable,ws_,"in",ws_,Array,ws,",",ws,Condition,ws,"]")
 3535        ]).
 3536
 3537%list comprehension without condition
 3538list_comprehension_1_(Data,[Var,Array,Result]) -->
 3539        langs_to_output(Data,list_comprehension_1,[
 3540        ['cython','python']:
 3541                ("[",python_ws,Result,python_ws_,"for",python_ws_,Var,python_ws_,"in",python_ws_,Array,python_ws,"]"),
 3542        ['php']:
 3543				("array_map",ws,"(",ws,"function",ws,"(",ws,Var,ws,")",ws,"{",ws,"return",ws,Result,ws,";",ws,"}",ws,",",ws,Array,ws,")")
 3544        ]).
 3545
 3546%list comprehension without condition
 3547all_true_(Data,[Var,Array,Condition]) -->
 3548        langs_to_output(Data,all_true,[
 3549        ['cython','python']:
 3550                ("all",python_ws,"(",python_ws,Condition,python_ws_,"for",python_ws_,Var,python_ws_,"in",python_ws_,Array,python_ws,")")
 3551        ]).
 3552
 3553startswith_(Data,[Str1,Str2]) -->
 3554        langs_to_output(Data,startswith,[
 3555        ['python']:
 3556                (Str1,python_ws,".",python_ws,"startswith",python_ws,"(",python_ws,Str2,python_ws,")"),
 3557        ['ruby']:
 3558                (Str1,ws,".",ws,"start_with?",ws,"(",ws,Str2,ws,")"),
 3559        ['java','javascript']:
 3560                (Str1,ws,".",ws,"startsWith",ws,"(",!,ws,Str2,ws,")"),
 3561        ['english_temp']:
 3562                (Str1,ws_,("starts";"begins"),ws_,"with",ws_,Str2),
 3563        ['swift']:
 3564                (Str1,ws,".",ws,"hasPrefix",ws,"(",ws,Str2,ws,")"),
 3565        ['go']:
 3566                ("strings",ws,".",ws,"hasPrefix",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")"),
 3567        ['haxe']:
 3568                ("StringTools",ws,".",ws,"startsWith",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")"),
 3569        ['c#','f#']:
 3570                (Str1,ws,".",ws,"StartsWith",ws,"(",ws,Str2,ws,")"),
 3571        ['julia']:
 3572                ("startswith",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")"),
 3573        ['haskell']:
 3574                ("(",ws,"isPrefixOf",ws_,Str1,ws_,Str2,ws,")"),
 3575        ['c']:
 3576                ("(",ws,"strncmp",ws,"(",ws,Str1,ws,",",ws,Str2,ws,",",ws,"strlen",ws,"(",ws,Str2,ws,")",ws,")",ws,"==",ws,"0",ws,")")
 3577        ]).
 3578
 3579endswith_(Data,[Str1,Str2]) -->
 3580        langs_to_output(Data,endswith,[
 3581        ['java','javascript']:
 3582                (Str1,ws,".",ws,"endsWith",ws,"(",!,ws,Str2,ws,")"),
 3583        ['ruby']:
 3584                (Str1,ws,".",ws,"end_with?",ws,"(",ws,Str2,ws,")"),
 3585        ['swift']:
 3586                (Str1,ws,".",ws,"hasSuffix",ws,"(",ws,Str2,ws,")"),
 3587        ['haxe']:
 3588                ("StringTools",ws,".",ws,"endsWith",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")"),
 3589        ['go']:
 3590                ("strings",ws,".",ws,"hasSuffix",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")"),
 3591        ['julia']:
 3592                ("endswith",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")"),
 3593        ['haskell']:
 3594                ("(",ws,"isSuffixOf",ws_,Str1,ws_,Str2,ws,")"),
 3595        ['cython','python']:
 3596                (Str1,python_ws,".",python_ws,"endswith",python_ws,"(",python_ws,Str2,python_ws,")"),
 3597        ['c#','f#']:
 3598                (Str1,ws,".",ws,"EndsWith",ws,"(",ws,Str2,ws,")")
 3599        ]).
 3600
 3601%remove extra whitespace at beginning and end of string
 3602% see https://www.rosettacode.org/wiki/Strip_whitespace_from_a_string
 3603trim_(Data,[Str]) -->
 3604        langs_to_output(Data,trim,[
 3605        ['java','javascript']:
 3606                (Str,ws,".",ws,"trim",ws,"(",!,ws,")"),
 3607        ['c#']:
 3608                (Str,ws,".",ws,"Trim",ws,"(",ws,")"),
 3609        ['python']:
 3610                (Str,python_ws,".",python_ws,"strip",python_ws,"(",python_ws,")"),
 3611        ['perl 6']:
 3612                (Str,ws,".",ws,"trim"),
 3613        ['ruby']:
 3614                (Str,ws,".",ws,"strip"),
 3615        ['php']:
 3616            ("trim",ws,"(",ws,Str,ws,")"),
 3617        ['clojure']:
 3618            ("(",ws,".trim",ws_,Str,ws,")"),
 3619        ['ocaml']:
 3620            ("(",ws,"String.trim",ws_,Str,ws,")"),
 3621        ['elixir']:
 3622                ("String",python_ws,".",python_ws,"strip",python_ws,"(",python_ws,Str,python_ws,")"),
 3623        ['lua']:
 3624				(Str,ws,":match(\"^%s*(.-)%s*$\")"),
 3625		['erlang']:
 3626				("string:strip",ws,"(",ws,Str,",",ws,"both",ws,")"),
 3627		['common lisp']:
 3628				("(",ws,"string-trim",ws_,Str,ws,")")
 3629        ]).
 3630
 3631% see https://www.rosettacode.org/wiki/Strip_whitespace_from_a_string
 3632lstrip_(Data,[Str]) -->
 3633        langs_to_output(Data,lstrip,[
 3634        ['python']:
 3635                (Str,python_ws,".",python_ws,"lstrip",python_ws,"(",python_ws,")"),
 3636        ['ruby']:
 3637                (Str,ws,".",ws,"lstrip"),
 3638        ['c#']:
 3639                (Str,ws,".",ws,"TrimStart",ws,"(",ws,")"),
 3640        ['php']:
 3641                ("ltrim",python_ws,"(",python_ws,Str,ws,")"),
 3642        ['elixir']:
 3643                ("String",python_ws,".",python_ws,"lstrip",python_ws,"(",python_ws,Str,python_ws,")"),
 3644        ['javascript']:
 3645				(Str,ws,".replace(/^\s+/,'')"),
 3646		['erlang']:
 3647				("string:strip",ws,"(",ws,Str,",",ws,"left",ws,")"),
 3648		['common lisp']:
 3649				("(",ws,"string-left-trim",ws_,Str,ws,")")
 3650        ]).
 3651
 3652% see https://www.rosettacode.org/wiki/Strip_whitespace_from_a_string
 3653rstrip_(Data,[Str]) -->
 3654        langs_to_output(Data,rstrip,[
 3655        ['python']:
 3656                (Str,python_ws,".",python_ws,"rstrip",python_ws,"(",python_ws,")"),
 3657        ['ruby']:
 3658                (Str,ws,".",ws,"rstrip"),
 3659        ['c#']:
 3660                (Str,ws,".",ws,"TrimEnd",ws,"(",ws,")"),
 3661        ['php']:
 3662                ("rtrim",python_ws,"(",python_ws,Str,ws,")"),
 3663        ['elixir']:
 3664                ("String",python_ws,".",python_ws,"rstrip",python_ws,"(",python_ws,Str,python_ws,")"),
 3665        ['javascript']:
 3666				(Str,ws,".replace(/\s+$/,'')"),
 3667		['erlang']:
 3668				("string:strip",ws,"(",ws,Str,",",ws,"right",ws,")"),
 3669		['common lisp']:
 3670				("(",ws,"string-right-trim",ws_,Str,ws,")")
 3671        ]).
 3672
 3673lowercase_(Data,[Str]) -->
 3674        langs_to_output(Data,lowercase,[
 3675        ['java','javascript','haxe','typescript']:
 3676                (Str,ws,".",ws,"toLowerCase",ws,"(",!,ws,")"),
 3677        ['c#']:
 3678                (Str,ws,".",ws,"ToLower",ws,"(",ws,")"),
 3679        ['systemverilog']:
 3680				(Str,ws,".",ws,"tolower",ws,"(",ws,")"),
 3681        ['perl']:
 3682                ("lc",ws,"(",ws,Str,ws,")"),
 3683        ['seed7','r','erlang']:
 3684                ("tolower",ws,"(",ws,Str,ws,")"),
 3685        ['mathematica']:
 3686                ("ToLowerCase",ws,"[",ws,Str,ws,"]"),
 3687        ['freebasic']:
 3688                ("lcase",ws,"(",ws,Str,ws,")"),
 3689        ['php']:
 3690                ("strtolower",ws,"(",ws,Str,ws,")"),
 3691        ['python']:
 3692				(Str,".",python_ws,"lower",python_ws,"(",python_ws,")"),
 3693		['ruby']:
 3694				(Str,ws,".",ws,"downcase"),
 3695		['lua']:
 3696				("string",ws,".",ws,"lower",ws,"(",ws,Str,ws,")")
 3697        ]).
 3698
 3699array_contains(Data,[Container,Contained]) -->
 3700        langs_to_output(Data,array_contains,[
 3701        ['python','julia','minizinc']:
 3702                (Contained,python_ws_,"in",python_ws_,Container),
 3703        ['english_temp']:
 3704                (
 3705					Contained,python_ws_,("in";"is",python_ws_,"in"),python_ws_,Container;
 3706					Container,python_ws_,"contains",python_ws_,Contained
 3707				),
 3708        ['swift']:
 3709                ("contains",ws,"(",ws,Container,ws,",",ws,Contained,ws,")"),
 3710        ['prolog']:
 3711                ("member",ws,"(",ws,Contained,ws,",",ws,Container,ws,")"),
 3712        ['lua']:
 3713                (Container,ws,"[",ws,Contained,ws,"]",ws,"~=",ws,"nil"),
 3714        ['rebol']:
 3715                ("not",ws_,"none?",ws_,"find",ws_,Container,ws_,Contained),
 3716        ['javascript','coffeescript','typescript']:
 3717                ("(",ws,Container,ws,".",ws,"indexOf",ws,"(",ws,Contained,ws,")",ws,"!==",ws,"-1",ws,")";
 3718                Container,ws,".",ws,"includes",ws,"(",ws,Contained,ws,")"),
 3719        ['coffeescript']:
 3720                (Contained,ws_,"in",ws_,Container;Container,ws,".",ws,"indexOf",ws,"(",ws,Contained,ws,")",ws,"!=",ws,"-1"),
 3721        ['ruby']:
 3722                (Container,ws,".",ws,"include?",ws,"(",ws,Contained,ws,")"),
 3723        ['haxe']:
 3724                ("Lambda",ws,".",ws,"has",ws,"(",ws,Container,ws,",",ws,Contained,ws,")"),
 3725        ['php']:
 3726                ("in_array",ws,"(",ws,Container,ws,",",ws,Container,ws,")"),
 3727        ['c#']:
 3728                (Container,ws,".",ws,"Contains",ws,"(",ws,Contained,ws,")"),
 3729        ['java']:
 3730                ("Arrays",ws,".",ws,"asList",ws,"(",ws,Container,ws,")",ws,".",ws,"contains",ws,"(",ws,Contained,ws,")"),
 3731        ['haskell']:
 3732                ("(",ws,"elem",ws_,Contained,ws_,Container,ws,")"),
 3733        ['c++']:
 3734                ("(",ws,"std",ws,"::",ws,"find",ws,"(",ws,"Std",ws,"(",ws,Container,ws,")",ws,",",ws,"std",ws,"::",ws,"end",ws,"(",ws,Container,ws,")",ws,",",ws,Contained,ws,")",ws,"!=",ws,"std",ws,"::",ws,"end",ws,"(",ws,Container,ws,")",ws,")")
 3735        ]).
 3736
 3737%Str1 contains Str2
 3738string_contains_(Data,[Str1,Str2]) -->
 3739        langs_to_output(Data,string_contains,[
 3740        ['c']:
 3741                ("(",ws,"strstr",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")",ws,"!=",ws,"NULL",ws,")"),
 3742        ['python']:
 3743				(Str2,python_ws_,"in",python_ws_,Str1),
 3744        ['java']:
 3745                (Str1,ws,".",ws,"contains",ws,"(",ws,Str2,ws,")"),
 3746        ['lua']:
 3747                ("str",ws,".",ws,"contains",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")"),
 3748        ['c#']:
 3749                (Str1,ws,".",ws,"Contains",ws,"(",ws,Str2,ws,")"),
 3750        ['perl']:
 3751                ("(",ws,"index",ws,"(",ws,Str1,ws,",",ws,Str2,ws,")",ws,"!=",ws,"-1",ws,")"),
 3752        ['javascript']:
 3753                ("(",ws,Str1,ws,".",ws,"indexOf",ws,"(",ws,Str2,ws,")",ws,(">";"!==";"!="),ws,"-1",ws,")"),
 3754        ['english']:
 3755				(
 3756					Str2,python_ws_,"is",python_ws_,"a",python_ws_,"substring",python_ws_,"of",python_ws_,Str1;
 3757					Str1,python_ws_,"contains",python_ws_,Str2
 3758				)
 3759        ]).
 3760
 3761
 3762this_(Data,[A]) -->
 3763    langs_to_output(Data,this,[
 3764    ['coffeescript','ruby']:
 3765            ("@",A),
 3766    ['java','engscript','dart','groovy','typescript','javascript','c#','c++','haxe','chapel','julia']:
 3767            ("this",ws,".",!,ws,A),
 3768    ['php','hack']:
 3769            ("$",ws,"this",ws,"->",ws,A),
 3770    ['swift','scala']:
 3771            (A),
 3772    ['rebol']:
 3773            ("self",ws,"/",ws,A),
 3774    ['python']:
 3775            ("self",python_ws,".",python_ws,A),
 3776    ['perl']:
 3777            ("$self",ws,"->",ws,A)
 3778    ]).
 3779
 3780access_dict_(Data,[Dict,Dict_,Index]) -->
 3781        langs_to_output(Data,access_dict,[
 3782        ['javascript','c++','haxe']:
 3783            ((Dict,ws,"[",ws,Index,ws,"]")),
 3784        ['python']:
 3785            (Dict,python_ws,"[",python_ws,Index,python_ws,"]"),
 3786        ['java']:
 3787            (Dict,ws,".",ws,"get",ws,"(",ws,Index,ws,")"),
 3788        ['english_temp']:
 3789			(
 3790				optional_the(Index),python_ws_,"of",python_ws_,Dict;
 3791				Dict,"'s",python_ws_,Index
 3792			),
 3793        ['perl']:
 3794            ("$",symbol(Dict_),ws,"{",ws,Index,ws,"}"),
 3795        % a dictionary in Java is a Map
 3796        ['java']:
 3797			(Dict,ws,".",ws,"get",ws,"(",ws,Index,ws,")")
 3798        ]).
 3799
 3800command_line_args_(Data) -->
 3801        langs_to_output(Data,command_line_args,[
 3802        ['perl']:
 3803                ("@ARGV"),
 3804        ['javascript']:
 3805                ("process",ws,".",ws,"argv",ws,".",ws,"slice",ws,"(",ws,"2",ws,")")
 3806        ]).
 3807
 3808call_constructor_(Data,[Name,Args]) -->
 3809    langs_to_output(Data,call_constructor,[
 3810    ['java','javascript','haxe','chapel','scala','php']:
 3811        ("new",ws_,Name,ws,"(",ws,Args,ws,")"),
 3812    ['visual basic','visual basic .net']:
 3813        ("New",ws_,Name,ws,"(",ws,Args,ws,")"),
 3814    ['perl','perl 6']:
 3815        (Name,ws,"->",ws,"new",ws,"(",ws,Args,ws,")"),
 3816    ['swift','octave']:
 3817        (Name,python_ws,"(",python_ws,Args,python_ws,")"),
 3818    ['c++']:
 3819        (Name,"::",Name,ws,"(",ws,Args,ws,")"),
 3820    ['hy']:
 3821        ("(",ws,Name,ws_,Args,ws,")")
 3822    ]).
 3823
 3824regex_matches_string_(Data,[Reg,Str]) -->
 3825        langs_to_output(Data,regex_matches_string,[
 3826        ['javascript']:
 3827            (Reg,ws,".",ws,"test",ws,"(",ws,Str,ws,")"),
 3828        ['c#']:
 3829            (Reg,ws,".",ws,"IsMatch",ws,"(",ws,Str,ws,")"),
 3830        ['haxe']:
 3831            (Reg,ws,".",ws,"match",ws,"(",ws,Str,ws,")")
 3832        ]).
 3833
 3834%shuffle an array in-place
 3835shuffle_array_(Data,[A]) -->
 3836        langs_to_output(Data,regex_matches_string,[
 3837        ['php']:
 3838            ("shuffle",ws,"(",ws,A,ws,")"),
 3839        ['python']:
 3840            ("random",python_ws,".",python_ws,"shuffle",python_ws,"(",python_ws,A,python_ws,")"),
 3841        ['ruby']:
 3842			(A,ws,"=",ws,A,ws,".",ws,"shuffle"),
 3843		['perl']:
 3844			(A,ws,"=",ws,"shuffle",ws,"(",ws,A,ws,")")
 3845        ]).
 3846
 3847dict_keys_(Data,[A]) -->
 3848        langs_to_output(Data,dict_keys,[
 3849            ['php']:
 3850                ("array_keys",ws,"(",ws,A,ws,")"),
 3851            ['perl']:
 3852                ("keys",ws,"(",ws,A,ws,")"),
 3853            ['swift']:
 3854                ("Array",ws,"(",ws,A,ws,".",ws,"keys",ws,")"),
 3855            ['swift']:
 3856                (A,python_ws,".",python_ws,"keys",python_ws,"(",python_ws,")"),
 3857            ['ruby']:
 3858                (A,ws,".",ws,"keys"),
 3859            ['python']:
 3860                (A,python_ws,".",python_ws,"keys",python_ws,"(",python_ws,")"),
 3861            ['javascript']:
 3862                ("Object",ws,".",ws,"keys",ws,"(",ws,A,ws,")"),
 3863            ['c#']:
 3864                ("new",ws_,"List<string>",ws,"(",ws,"this",ws,".",ws,A,ws,".","Keys",ws,")")
 3865        ]).
 3866
 3867compare_arrays_(Data,[A,B]) -->
 3868        langs_to_output(Data,compare_arrays,[
 3869            ['cython','ruby']:
 3870                (A,python_ws,"==",python_ws,B),
 3871            ['c++']:
 3872                ("std::equal(std::begin(",ws,A,ws,"),std::end(",ws,A,ws,"),std::begin(",ws,B,ws,"))"),
 3873            ['php']:
 3874                (A,ws,"===",ws,B),
 3875            ['c#']:
 3876                (A,ws,".",ws,"SequenceEqual",ws,"(",ws,B,ws,")"),
 3877            ['java']:
 3878                ("Arrays",ws,".",ws,"deepEquals",ws,"(",ws,A,ws,",",ws,B,ws,")")
 3879        ]).
 3880
 3881%replace a string (not in-place)
 3882global_replace_in_string_(Data,[Str,Sub,Replacement]) -->
 3883        langs_to_output(Data,global_replace_in_string,[
 3884            ['cython','python','java']:
 3885                (Str,python_ws,".",python_ws,"replace",python_ws,"(",python_ws,Sub,python_ws,",",python_ws,Replacement,python_ws,")"),
 3886            ['c++']:
 3887				(Str,ws,".",ws,"replace",ws,"(",ws,"s",ws,".",ws,"find",ws,"(",ws,Sub,ws,")",ws,",",Sub,".",ws,"length",ws,"(",ws,")",ws,",",ws,Replacement,ws,")"),
 3888            ['php']:
 3889                ("str_replace",ws,"(",ws,Sub,ws,",",ws,Replacement,ws,",",ws,Str,ws,")"),
 3890            ['javascript']:
 3891                (Str,ws,".",ws,"split",ws,"(",ws,Sub,ws,")",ws,".",ws,"join",ws,"(",ws,Replacement,ws,")"),
 3892            ['coffeescript']:
 3893                (Str,python_ws,".",python_ws,"split",python_ws,"(",python_ws,Sub,python_ws,")",python_ws,".",python_ws,"join",python_ws,"(",python_ws,Replacement,python_ws,")"),
 3894            ['c#']:
 3895                (Str,ws,".",ws,"Replace",ws,"(",ws,Sub,ws,",",ws,Replacement,ws,")"),
 3896            ['ruby']:
 3897                (Str,ws,".",ws,"gsub",ws,"(",ws,Sub,ws,")"),
 3898            ['swift']:
 3899                (Str,ws,".",ws,"stringByReplacingOccurrencesOfString",ws,"(",ws,Sub,ws,",",ws,"withString:",ws,Replacement,ws,")"),
 3900            ['haxe']:
 3901                ("StringTools",ws,".",ws,"replace",ws,"(",ws,Str,ws,",",ws,Sub,ws,Replacement,ws,")")
 3902        ]).
 3903
 3904%get the first index of a substring
 3905index_of_substring_(Data,[String,Substring]) -->
 3906    langs_to_output(Data,index_of_substring,[
 3907    ['javascript','java']:
 3908        (String,ws,".",ws,"indexOf",ws,"(",ws,Substring,ws,")"),
 3909    ['d']:
 3910        (String,ws,".",ws,"indexOfAny",ws,"(",ws,Substring,ws,")"),
 3911    ['c#']:
 3912        (String,ws,".",ws,"IndexOf",ws,"(",ws,Substring,ws,")"),
 3913    ['cython','python']:
 3914        (String,python_ws,".",python_ws,"index",python_ws,"(",python_ws,Substring,python_ws,")"),
 3915    ['go']:
 3916        ("strings",ws,".",ws,"Index",ws,"(",ws,String,ws,",",ws,Substring,ws,")"),
 3917    ['perl']:
 3918        ("index",ws,"(",ws,String,ws,",",ws,Substring,ws,")")
 3919    ]).
 3920
 3921substring_(Data,[A,B,C]) -->
 3922        langs_to_output(Data,substring,[
 3923        ['javascript','coffeescript','typescript','java','scala','dart']:
 3924                (A,ws,".",ws,"substring",ws,"(",ws,B,ws,",",ws,C,ws,")"),
 3925        ['c++']:
 3926                (A,ws,".",ws,"substring",ws,"(",ws,B,ws,",",ws,C,ws,"-",ws,B,ws,")"),
 3927        ['z3']:
 3928                ("(",ws,"Substring",ws_,A,ws_,B,ws_,C,ws,")"),
 3929        ['cython','icon','go']:
 3930                (A,python_ws,"[",python_ws,B,python_ws,":",python_ws,C,python_ws,"]"),
 3931        ['julia:']:
 3932                (A,ws,"[",ws,B,ws,"-",ws,"1",ws,":",ws,C,ws,"]"),
 3933        ['fortran']:
 3934                (A,ws,"(",ws,B,ws,":",ws,C,ws,")"),
 3935        ['c#','nemerle']:
 3936                (A,ws,".",ws,"Substring",ws,"(",ws,B,ws,",",ws,C,ws,")"),
 3937        ['haskell']:
 3938                ("take",ws,"(",ws,C,ws,"-",ws,B,ws,")",ws,".",ws,"drop",ws,B,ws,"$",ws,A),
 3939        ['php','awk','perl','hack']:
 3940                ("substr",ws,"(",ws,A,ws,",",ws,B,ws,",",ws,C,ws,")"),
 3941        ['haxe']:
 3942                (A,ws,".",ws,"substr",ws,"(",ws,B,ws,",",ws,C,ws,")"),
 3943        ['rebol']:
 3944                ("copy/part",ws_,"skip",ws_,A,ws_,B,ws_,C),
 3945        ['clojure']:
 3946                ("(",ws,"subs",ws_,A,ws_,B,ws_,C,ws,")"),
 3947        ['erlang']:
 3948                ("string",ws,":",ws,"sub_string",ws,"(",ws,A,ws,",",ws,B,ws,",",ws,C,ws,")"),
 3949        ['pike','groovy']:
 3950                (A,ws,"[",ws,B,ws,"..",ws,C,ws,"]"),
 3951        ['racket']:
 3952                ("(",ws,"substring",ws_,A,ws_,B,ws_,C,ws,")"),
 3953        ['common lisp']:
 3954                ("(",ws,"subseq",ws_,A,ws_,B,ws_,C,ws,")")
 3955        ]).
 3956
 3957not_(Data,[A]) -->
 3958        langs_to_output(Data,'not',[
 3959        ['python','lua','!','cython','pddl','mathematical notation','emacs lisp','minizinc','picat','genie','seed7','z3','idp','maxima','clips','engscript','hy','ocaml','clojure','erlang','pascal','delphi','f#','ml','racket','common lisp','rebol','haskell','sibilant']:
 3960                ("(",python_ws,"not",python_ws_,A,python_ws,")"),
 3961        ['java','ruby','perl 6','katahdin','coffeescript','frink','d','ooc','ceylon','processing','janus','pawn','autohotkey','groovy','scala','hack','rust','octave','typescript','julia','awk','swift','scala','vala','nemerle','pike','perl','c','c++','objective-c','tcl','javascript','r','dart','java','go','php','haxe','c#','wolfram']:
 3962                ("!",A),
 3963        ['prolog']:
 3964                ("\\+",A),
 3965        ['visual basic','autoit','livecode','monkey x','vbscript']:
 3966                ("(",ws,"Not",ws_,A,ws,")"),
 3967        ['fortran']:
 3968                (".NOT.",A),
 3969        ['gambas']:
 3970                ("NOT",ws_,A),
 3971        ['rexx']:
 3972                ("\\",A),
 3973        ['pl/i']:
 3974                ("^",A),
 3975        ['powershell']:
 3976                ("-not",ws_,A),
 3977        ['polish notation']:
 3978                ("not",ws_,A,ws_,"b"),
 3979        ['reverse polish notation']:
 3980                (A,ws_,"not"),
 3981        ['z3py']:
 3982                ("Not",ws,"(",ws,A,ws,")")
 3983        ]).
 3984
 3985and_(Data,[A,B]) -->
 3986    langs_to_output(Data,'and',[
 3987    ['javascript','ats','ruby','katahdin','perl 6','wolfram','chapel','elixir','frink','ooc','picat','janus','processing','pike','nools','pawn','matlab','hack','gosu','rust','autoit','autohotkey','typescript','ceylon','groovy','d','octave','awk','julia','scala','f#','swift','nemerle','vala','go','perl','java','haskell','haxe','c','c++','c#','dart','r']:
 3988            (A,ws,"&&",ws,B),
 3989    ['pydatalog']:
 3990            (A,ws,"&",ws,B),
 3991    ['seed7','vhdl','cython','python','lua','livecode','englishscript','cython','gap','mathematical notation','genie','idp','maxima','engscript','ada','newlisp','ocaml','nim','coffeescript','pascal','delphi','erlang','rebol','php']:
 3992            (A,python_ws_,"and",python_ws_,B),
 3993    ['english']:
 3994            (A,python_ws_,synonym("and"),python_ws_,B),
 3995    ['minizinc']:
 3996            (A,ws,"/\\",ws,B),
 3997    ['fortran']:
 3998            (A,ws,".AND.",ws,B),
 3999    ['common lisp','pddl','z3','newlisp','racket','clojure','sibilant','hy','clips','emacs lisp']:
 4000            ("(",ws,"and",ws_,A,ws_,B,ws,")"),
 4001    ['prolog']:
 4002            (A,ws,",",ws,B),
 4003    ['visual basic','vbscript','openoffice basic','monkey x','visual basic .net']:
 4004            (A,ws_,"And",ws_,B),
 4005    ['polish notation']:
 4006            ("and",ws_,A,ws_,B),
 4007    ['reverse polish notation']:
 4008            (A,ws_,B,ws_,"and"),
 4009    ['z3py','pysmt']:
 4010            ("And",python_ws,"(",python_ws,A,python_ws,",",python_ws,B,python_ws,")")
 4011    ]).
 4012
 4013sort_in_place_(Data,[List]) -->
 4014        langs_to_output(Data,sort_in_place,[
 4015			['ocaml']:
 4016				(
 4017					%this is for lists
 4018					"(",ws,"List.sort",ws_,List,ws,")";
 4019					%this is for arrays
 4020					"(",ws,"Array.sort",ws_,List,ws,")"
 4021				),
 4022			['python','javascript']:
 4023				(List,python_ws,".",python_ws,"sort",python_ws,"(",python_ws,")"),
 4024			['ruby']:
 4025				(List,ws,".",ws,"sort!"),
 4026			['c++']:
 4027				("std::sort",ws,"(",ws,"std::begin",ws,"(",ws,List,ws,")",ws,",",ws,"std::end",ws,"(",ws,List,ws,")",ws,")"),
 4028			['php']:
 4029				("sort",ws,"(",ws,List,ws,")"),
 4030			['lua']:
 4031				("table",ws,".",ws,"sort",ws,"(",ws,List,ws,")"),
 4032			['perl']:
 4033				(List,ws,"=",ws,"sort",ws_,List)
 4034        ]).
 4035
 4036reverse_sort_in_place_(Data,[List]) -->
 4037        langs_to_output(Data,rsort_in_place,[
 4038			['php']:
 4039				("rsort",ws,"(",ws,List,ws,")"),
 4040			['python']:
 4041				(List,python_ws,".",python_ws,"sort",python_ws,"(",python_ws,"reverse",python_ws,"=",python_ws,"True",python_ws,")"),
 4042			['javascript']:
 4043				(List,ws,".",ws,"sort",ws,"(",ws,")",ws,".",ws,"reverse",ws,"(",ws,")")
 4044        ]).
 4045
 4046uppercase_(Data,[Str]) -->
 4047        langs_to_output(Data,uppercase,[
 4048        ['perl']:
 4049                ("uc",ws,"(",ws,Str,ws,")"),
 4050        ['php']:
 4051                ("strtoupper",ws,"(",ws,Str,ws,")"),
 4052        ['julia']:
 4053                ("uppercase",ws,"(",ws,Str,ws,")"),
 4054        ['java','javascript','haxe']:
 4055                (Str,ws,".",ws,"toUpperCase",ws,"(",ws,")"),
 4056        ['c#']:
 4057                (Str,ws,".",ws,"UpperCase",ws,"(",ws,")"),
 4058        ['python']:
 4059				(Str,python_ws,".",python_ws,"upper",python_ws,"(",python_ws,")"),
 4060		['systemverilog']:
 4061				(Str,ws,".",ws,"toupper",ws,"(",ws,")"),
 4062		['ruby']:
 4063				(Str,ws,".",ws,"upcase"),
 4064		['lua']:
 4065				("string",ws,".",ws,"upper",ws,"(",ws,Str,ws,")"),
 4066		['r']:
 4067				("toupper",ws,"(",ws,Str,ws,")")
 4068        ]).
 4069
 4070char_to_uppercase_(Data,[Str]) -->
 4071        langs_to_output(Data,char_to_uppercase,[
 4072        ['java']:
 4073                ("Character",ws,".",ws,"toUpperCase",ws,"(",Str,ws,")"),
 4074        ['c']:
 4075				("toupper",ws,"(",ws,Str,ws,")")
 4076        ]).
 4077
 4078char_to_lowercase_(Data,[Str]) -->
 4079        langs_to_output(Data,char_to_lowercase,[
 4080        ['java']:
 4081                ("Character",ws,".",ws,"toLowerCase",ws,"(",Str,ws,")"),
 4082        ['c']:
 4083				("tolower",ws,"(",ws,Str,ws,")")
 4084        ]).
 4085        
 4086% see https://rosettacode.org/wiki/Real_constants_and_functions
 4087pi_(Data) -->
 4088    langs_to_output(Data,pi,[
 4089    ['java','pseudocode','javascript','c#']:
 4090            ("Math",ws,".",ws,"PI"),
 4091    ['pseudocode','python']:
 4092            ("math",python_ws,".",python_ws,"pi"),
 4093    ['php']:
 4094			"M_PI",
 4095	['erlang','perl 6']:
 4096			"pi"
 4097    ]).
 4098     
 4099grammar_or_(Data,[Var1,Var2]) -->
 4100    langs_to_output(Data,grammar_or,[
 4101    ['lpeg']:
 4102		(Var1,ws,"+",ws,Var2),
 4103    ['marpa','wirth syntax notation','rebol','yapps','antlr','jison','waxeye','ometa','ebnf','nearley','parslet','yacc','perl 6','rebol','hampi','earley-parser-js']:
 4104            (Var1,ws,"|",ws,Var2),
 4105    ['lpeg']:
 4106            (Var1,ws,"+",ws,Var2),
 4107    ['peg.js','abnf','treetop']:
 4108            (Var1,ws,"/",ws,Var2),
 4109    ['prolog','definite clause grammars']:
 4110            (Var1,ws,";",!,ws,Var2)
 4111    ]).
 4112
 4113grammar_and_(Data,[Var1,Var2]) -->
 4114    langs_to_output(Data,grammar_and,[
 4115	['definite clause grammars','pypeg']:
 4116            (Var1,ws,",",ws,Var2),
 4117    ['lpeg']:
 4118            (Var1,ws,"*",ws,Var2),
 4119    ['nearley','abnf','coco/r','peg.js','antlr','marpa','wirth syntax notation','canopy']:
 4120            (Var1,ws_,Var2)
 4121    ]).
 4122
 4123eager_and_(Data,[Var1,Var2]) -->
 4124    langs_to_output(Data,'eager_or',[
 4125	['javascript','python','c++','c#','php','smalltalk','perl','ruby','java','julia','matlab','r','swift']:
 4126        (Var1,python_ws,"&",python_ws,Var2),
 4127    ['erlang','pascal']:
 4128		(Var1,ws_,"and",ws_,Var2),
 4129	['visual basic','visual basic .net','VBScript']:
 4130		(Var1,ws_,"And",ws_,Var2)
 4131    ]).
 4132
 4133eager_or_(Data,[Var1,Var2]) -->
 4134    langs_to_output(Data,'eager_or',[
 4135	['javascript','python','c++','c#','php','smalltalk','perl','ruby','java','julia','matlab','r','swift']:
 4136        (Var1,python_ws,"|",python_ws,Var2),
 4137    ['erlang','pascal']:
 4138		(Var1,ws_,"or",ws_,Var2),
 4139	['visual basic','visual basic .net','VBScript']:
 4140		(Var1,ws_,"Or",ws_,Var2)
 4141    ]).
 4142
 4143or_(Data,[Var1,Var2]) -->
 4144    langs_to_output(Data,'or',[
 4145    ['javascript','katahdin','perl 6','ruby','wolfram','chapel','elixir','frink','ooc','picat','janus','processing','pike','nools','pawn','matlab','hack','gosu','rust','autoit','autohotkey','typescript','ceylon','groovy','d','octave','awk','julia','scala','f#','swift','nemerle','vala','go','perl','java','haskell','haxe','c','c++','c#','dart',r]:
 4146        (Var1,ws,"||",!,ws,Var2),
 4147    ['cosmos','cython','vhdl','python','lua','seed7','pydatalog','livecode','englishscript','cython','gap','mathematical notation','genie','idp','maxima','engscript','ada','newlisp','ocaml','nim','coffeescript','pascal','delphi','erlang','rebol','php']:
 4148        (Var1,python_ws_,"or",python_ws_,Var2),
 4149	['english']:	
 4150		(Var1,python_ws_,"or",python_ws_,Var2),
 4151    ['fortran']:
 4152        (Var1,ws_,".OR.",ws_,Var2),
 4153    ['z3','clips','pddl','clojure','common lisp','emacs lisp','clojure','racket']:
 4154        ("(",ws,"or",ws_,Var1,ws_,Var2,ws,")"),
 4155    ['prolog']:
 4156        (Var1,ws,";",!,ws,Var2),
 4157    ['minizinc']:
 4158        (Var1,ws,"\\/",ws,Var2),
 4159    ['visual basic','monkey x','visual basic .net']:
 4160        (Var1,ws_,"Or",ws_,Var2)
 4161    ]).
 4162
 4163last_index_of_(Data,[String,Substring]) -->
 4164    langs_to_output(Data,last_index_of,[
 4165    ['haxe','java','kotlin','haxe']:
 4166        (String,ws,".",ws,"lastIndexOf",ws,"(",ws,Substring,ws,")"),
 4167    ['c++']:
 4168        (String,ws,".",ws,"find_last_of",ws,"(",ws,Substring,ws,")"),
 4169    ['perl']:
 4170        ("rindex",ws,"(",ws,String,ws,",",ws,Substring,ws,")"),
 4171    ['c#']:
 4172        (String,ws,".",ws,"LastIndexOf",ws,"(",ws,Substring,ws,")")
 4173    ]).
 4174
 4175
 4176optional_indent(Data,Indent) -->
 4177	{Data = [Lang,_,_,Indent],
 4178	offside_rule_langs(Offside_rule_langs)},
 4179	{memberchk(Lang,Offside_rule_langs)}->
 4180		Indent;
 4181	(Indent;"").
 4182
 4183%This creates variables without initializing them.
 4184declare_vars_(Data,[Vars,Type]) -->
 4185	langs_to_output(Data,declare_vars,[
 4186    ['javascript']:
 4187		("var",ws_,Vars),
 4188	['perl']:
 4189		("my",ws_,Vars),
 4190	['c','c++']:
 4191		(Type,ws_,Vars),
 4192	['swift']:
 4193		("var",ws_,Vars,ws,":",ws,Type)
 4194    ]).
 4195
 4196%This creates each variable with a value.
 4197initialize_vars_(Data,[Vars,Type]) -->
 4198	langs_to_output(Data,initialize_vars,[
 4199    ['javascript']:
 4200		("var",ws_,Vars),
 4201	['perl']:
 4202		("my",ws_,Vars),
 4203	['c','c++']:
 4204		(Type,ws_,Vars)
 4205    ]).
 4206
 4207
 4208set_same_value_(Data,[Vars,Expr,Type]) -->
 4209	langs_to_output(Data,set_same_value,[
 4210	['java']:
 4211		(Vars,ws,"=",ws,Expr),
 4212	['perl']:
 4213		(Vars,ws,"=",Vars)
 4214    ]).
 4215
 4216
 4217%this does not initialize the variables
 4218multiple_assignment_(Data,[Vars,Exprs,Type]) -->
 4219	langs_to_output(Data,multiple_assignment,[
 4220		['python_temp','lua','ruby']:
 4221			set_var_(Data,[Vars,Exprs]),
 4222		['perl']:
 4223			("(",Vars,")",ws,"=",ws,Exprs),
 4224		['prolog','swift']:
 4225			("(",ws,Vars,ws,")",ws,"=",ws,"(",Exprs,")")
 4226    ]).
 4227
 4228instanceof_(Data,[Expr,Type,_]) -->
 4229	langs_to_output(Data,instanceof,[
 4230		['swift','c#']:
 4231			(Expr,ws_,"is",ws_,Type),
 4232		['java']:
 4233			(Expr,ws_,"instanceof",ws_,Type)
 4234	]).
 4235
 4236instanceof_([php|_],[Expr,Type,Type2]) -->
 4237	{Type2 = bool}->("is_bool",ws,"(",ws,Expr,ws,")"),
 4238	{Type2 = float}->("is_float",ws,"(",ws,Expr,ws,")"),
 4239	{Type2 = int}->("is_int",ws,"(",ws,Expr,ws,")"),
 4240	{Type2 = string}->("is_string",ws,"(",ws,Expr,ws,")").
 4241
 4242instanceof_([prolog|_],[Expr,Type,Type2]) -->
 4243	{Type2 = float}->("float",ws,"(",ws,Expr,ws,")"),
 4244	{Type2 = int}->("integer",ws,"(",ws,Expr,ws,")"),
 4245	{Type2 = string}->("string",ws,"(",ws,Expr,ws,")").
 4246
 4247try_catch_(Data,[Body1,Name,Body2,Indent]) -->
 4248	langs_to_output(Data,try_catch,[
 4249		['javascript']:
 4250			("try",ws,"{",ws,Body1,ws,"}",ws,"catch",ws,"(",ws,Name,ws,")",ws,"{",ws,Body2,ws,"}"),
 4251		['python_temp']:
 4252			("try:",python_ws,Body1,Indent,"except",python_ws_,"Exception",python_ws_,"as",python_ws,Name,":",python_ws,Body2),
 4253		['java','c#','php']:
 4254			("try",ws,"{",ws,Body1,ws,"}",ws,"catch",ws,"(",ws,"Exception",ws_,Name,ws,")",ws,"{",ws,Body2,ws,"}")
 4255	]).
 4256
 4257%see https://rosettacode.org/wiki/Sort_an_integer_array#C.23
 4258%sort a list of integers (not in-place)
 4259sort_(Data,[List]) -->
 4260	langs_to_output(Data,sort,[
 4261		['lua']:
 4262			("table",ws,".",ws,"sort",ws,"(",ws,List,ws,")"),
 4263		['ruby']:
 4264			(List,ws,".",ws,"sort"),
 4265		['perl']:
 4266			("sort",ws,"(",ws,List,ws,")"),
 4267		['python','cython']:
 4268			("sorted",python_ws,"(",python_ws,List,python_ws,")"),
 4269		['prolog']:
 4270			("(",ws,"sort",ws_,"$",ws,"(",ws,List,ws,")",ws,")"),
 4271		%in ocaml, this function sorts an array or a list
 4272		['ocaml']:
 4273			(
 4274				%this is for lists
 4275				"(",ws,"List.sort",ws_,List,ws,")";
 4276				%this is for arrays
 4277				"(",ws,"Array.sort",ws_,List,ws,")"
 4278			),
 4279		['haskell']:
 4280			("(",ws_,"sort",ws_,"compare",ws_,List,ws_,")"),
 4281		['javascript']:
 4282			(List,ws,".",ws,"sort",ws,"(",ws,")"),
 4283		['c#']:
 4284			(List,ws,".",ws,"Sort",ws,"(",ws,")")
 4285	]).
 4286
 4287%Returns the MD5 checksum as a hexadecimal string.
 4288% see https://rosettacode.org/wiki/MD5
 4289md5_(Data,[Str]) -->
 4290	langs_to_output(Data,md5,[
 4291		['php']:
 4292			("md5",ws,"(",ws,Str,ws,")")
 4293	]).
 4294
 4295%Returns the SHA-1 hash as a hexadecimal string.
 4296% see https://rosettacode.org/wiki/SHA-1#C.2B.2B
 4297sha1_(Data,[Str]) -->
 4298	langs_to_output(Data,sha1,[
 4299		['php']:
 4300			("sha1",ws,"(",ws,Str,ws,")"),
 4301		['d']:
 4302			(Str,ws,".",ws,"sha1Of"),
 4303		['erlang']:
 4304			("crypto:hash",ws,"(",ws,"sha",ws,",",ws,Str,ws,")"),
 4305		['ruby']:
 4306			("Digest::SHA1.hexdigest",ws,"(",ws,Str,ws,")")
 4307	]),!.
 4308
 4309ing(Data,[Object]) -->
 4310	langs_to_output(Data,ing,[
 4311		['python']:
 4312			("type",python_ws,"(",python_ws,Object,python_ws,")",(ws_,"is",ws_;ws,"==",ws),"\"str\"";
 4313			"\"str\"",(ws_,"is",ws_;ws,"==",ws),"type",python_ws,"(",python_ws,Object,python_ws,")"),
 4314		['ruby']:
 4315			(Object,ws,".instance_of?",ws_,"String"),
 4316		['php']:
 4317			("is_string",ws,"(",ws,Object,ws,")"),
 4318		['java']:
 4319			(Object,ws_,"instanceof",ws_,"String"),
 4320		['c#']:
 4321			(Object,ws_,"is",ws_,"String"),
 4322		['lua']:
 4323			("type",ws,"(",ws,Object,python_ws,")",ws,"==",ws,"\"string\"";
 4324			"\"string\"",ws,"==",ws,"type",ws,"(",ws,Object,ws,")"),
 4325		['javascript']:
 4326			(Object,ws_,"instanceof",ws_,"String",ws,"||",ws,"typeof",ws_,Object,ws,"===",ws,"\"string\"")
 4327	]),!.
 4328
 4329type_is_bool(Data,[Object]) -->
 4330	langs_to_output(Data,type_is_bool,[
 4331		['python']:
 4332			("type",python_ws,"(",python_ws,Object,python_ws,")",(ws_,"is",ws_;ws,"==",ws),"\"boolean\"";
 4333			"\"boolean\"",(ws_,"is",ws_;ws,"==",ws),"type",python_ws,"(",python_ws,Object,python_ws,")"),
 4334		['ruby']:
 4335			("[",ws,"true",ws,",",ws,"false",ws,"]",ws,".",ws,"include?",ws_,Object),
 4336		['php']:
 4337			("is_bool",ws,"(",ws,Object,ws,")"),
 4338		['lua']:
 4339			("type",ws,"(",ws,Object,python_ws,")",ws,"==",ws,"\"boolean\"";
 4340			"\"boolean\"",ws,"==",ws,"type",ws,"(",ws,Object,ws,")"),
 4341		['javascript']:
 4342			("typeof",ws,"(",ws,Object,python_ws,")",ws,"==",ws,"\"boolean\"";
 4343			"\"boolean\"",ws,"==",ws,"typeof",ws,"(",ws,Object,ws,")")
 4344	]),!.
 4345
 4346type_is_int(Data,[Object]) -->
 4347	langs_to_output(Data,type_is_int,[
 4348		['python']:
 4349			("type",python_ws,"(",python_ws,Object,python_ws,")",(ws_,"is",ws_;ws,"==",ws),"\"int\"";
 4350			"\"int\"",(ws_,"is",ws_;ws,"==",ws),"type",python_ws,"(",python_ws,Object,python_ws,")"),
 4351		['prolog']:
 4352			("integer",ws,"(",ws,Object,ws,")"),
 4353		['php']:
 4354			("is_int",ws,"(",ws,Object,ws,")"),
 4355		['ruby']:
 4356			(Object,ws,".instance_of?",ws_,"Integer")
 4357	]),!.
 4358
 4359type_is_list(Data,[Object]) -->
 4360	langs_to_output(Data,type_is_list,[
 4361		['python']:
 4362			("type",python_ws,"(",python_ws,Object,python_ws,")",(ws_,"is",ws_;ws,"==",ws),"list";
 4363			"list",(ws_,"is",ws_;ws,"==",ws),"type",python_ws,"(",python_ws,Object,python_ws,")"),
 4364		['lua']:
 4365			("type",ws,"(",ws,Object,python_ws,")",ws,"==",ws,"\"table\"";
 4366			"\"table\"",ws,"==",ws,"type",ws,"(",ws,Object,ws,")"),
 4367		['javascript']:
 4368			("Array",ws,".",ws,"isArray(",ws,Object,ws,")"),
 4369		['prolog']:
 4370			("is_list",ws_,"(",ws,Object,ws,")"),
 4371		['ruby']:
 4372			(Object,ws,".",ws,"instance_of?",ws_,"Array"),
 4373		['php']:
 4374			("is_array",ws,"(",ws,Object,ws,")"),
 4375		['perl']:
 4376			("ref",ws,"(",ws,Object,ws,")",ws_,"eq",ws_,"'ARRAY'")
 4377	]),!