123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724(* PG'OCaml - type safe interface to PostgreSQL.
* Copyright (C) 2005-2016 Richard Jones and other authors.
*
* This library is free software; you can redistribute it and/or
* modify it under the terms of the GNU Library General Public
* License as published by the Free Software Foundation; either
* version 2 of the License, or (at your option) any later version.
*
* This library is distributed in the hope that it will be useful,
* but WITHOUT ANY WARRANTY; without even the implied warranty of
* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
* Library General Public License for more details.
*
* You should have received a copy of the GNU General Public License
* along with this library; see the file COPYING. If not, write to
* the Free Software Foundation, Inc., 59 Temple Place - Suite 330,
* Boston, MA 02111-1307, USA.
*)openPGOCaml_auxopenPpxlibopenAst_helperopenAsttypesopenParsetreeletnullable_name="nullable"letunravel_name="unravel"lettypname_name="typname"(* We need a database connection while compiling. If people use the
* override flags like "database=foo", then we may connect to several
* databases at once. Keep track of that here. Note that in the normal
* case we have just one database handle, opened to the default
* database (as controlled by environment variables such as $PGHOST,
* $PGDATABASE, etc.)
*)typekey=PGOCaml.connection_descletconnections:(key,unitPGOCaml.t)Hashtbl.t=Hashtbl.create16[%%ifocaml_version<(4,08,0)]letexp_of_string~loc:_x=letlexer=Lexing.from_stringxinParse.expressionlexer[%%else]letexp_of_string~locx=letlexer=letacc=Lexing.from_string~with_positions:falsexinacc.Lexing.lex_start_p<-loc.loc_start;acc.Lexing.lex_curr_p<-loc.loc_end;accinParse.expressionlexer[%%endif](** [get_connection key] Find the database connection specified by [key],
* otherwise attempt to create a new one from [key] and return that (or an
* error).
*)letget_connection~lockey=matchHashtbl.find_optconnectionskeywith|Someconnection->letopenRresultinOkconnection|None->(* Create a new connection. *)tryletdbh=PGOCaml.connect~desc:key()in(* Prepare the nullable test - see result conversions below. *)letnullable_query="select attnotnull from pg_attribute where attrelid = $1 and attnum = $2"inPGOCaml.preparedbh~query:nullable_query~name:nullable_name();(* Prepare the unravel test. *)letunravel_query="select typname, typtype, typbasetype from pg_type where oid = $1"inPGOCaml.preparedbh~query:unravel_query~name:unravel_name();(* Prepare the type name query. *)lettypname_query="select typname from pg_type where oid = $1"inPGOCaml.preparedbh~query:typname_query~name:typname_name();Hashtbl.addconnectionskeydbh;Rresult.Okdbhwith|err->Error("Could not make the connection "^PGOCaml.connection_desc_to_stringkey^", error: "^Printexc.to_stringerr,loc)(* Wrapper around [PGOCaml.name_of_type].
*)letname_of_type_wrapperdbhoid=trySome(PGOCaml.name_of_typeoid)withPGOCaml.Error_->letparams=[Some(PGOCaml.string_of_oidoid)]inletrows=PGOCaml.executedbh~name:typname_name~params()inmatchrowswith|[[Some"citext"]]->Some"string"|[[Some"hstore"]]->Some"hstore"|_->None(* By using CREATE DOMAIN, the user may define types which are essentially aliases
* for existing types. If the original type is not recognised by PG'OCaml, this
* functions recurses through the pg_type table to see if it happens to be an alias
* for a type which we do know how to handle.
*)letunravel_typedbh?load_custom_from?colnam?argnam?typnamorig_type=letget_customtypnam=matchPGOCaml.find_custom_typconvs?typnam?lookin:load_custom_from?colnam?argnam()with|Okconvs->Option.default"FIXME"typnam,convs|Errorexc->failwithexcinletrecunravel_type_auxft=letrv=letrv=matchtypnamwith|Somex->Somex,None|None->name_of_type_wrapperdbhft,NoneinmatchPGOCaml.find_custom_typconvs?typnam:(fstrv)?lookin:load_custom_from?colnam?argnam()with|Ok(x)->(fstrv),x|Errorerr->failwitherrinmatchrvwith|None,_->letparams=[Some(PGOCaml.string_of_oidft)]inletrows=PGOCaml.executedbh~name:unravel_name~params()inbeginmatchrowswith|[typnam::_]whenRresult.R.is_ok(PGOCaml.find_custom_typconvs?typnam?lookin:load_custom_from?colnam?argnam())->get_customtypnam|[[Some_;Sometyptype;_]]whentyptype="e"->"string",None|[[Some_;Sometyptype;Sometypbasetype]]whentyptype="d"->unravel_type_aux(PGOCaml.oid_of_stringtypbasetype)|_->failwith"Impossible"end|typnam,coders->Option.default"FIXME"typnam,codersinunravel_type_auxorig_type(* Return the list of numbers a <= i < b. *)letrecrangeab=ifa<bthena::range(a+1)belse[]letrex=letopenRein[char'$';opt(group(char'@'));opt(group(char'?'));group(alt[seq[alt[char'_';rg'a''z'];rep(alt[char'_';char'\'';rg'a''z';rg'A''Z';rg'0''9'])];seq[char'{';rep(diffany(char'}'));char'}']])]|>seq|>compileletloc_raise_locexn=raiseexnletconst_string~locstr={pexp_desc=Pexp_constant(Pconst_string(str,loc,None));pexp_loc=loc;pexp_attributes=[];pexp_loc_stack=[]}letparse_flagsflagsloc=letf_execute=reffalseinletf_nullable_results=reffalseinlethost=refNoneinletport=refNoneinletuser=refNoneinletpassword=refNoneinletdatabase=refNoneinletunix_domain_socket_dir=refNoneinletcomment_src_loc=ref(PGOCaml.comment_src_loc())inletshow=refNoneinletload_custom_from=refNoneinList.iter(function|"execute"->f_execute:=true|"nullable-results"->f_nullable_results:=true|"show"->show:=Some"show"|strwhenString.starts_withstr"host="->lethost'=String.substr5(String.lengthstr-5)inhost:=Somehost'|strwhenString.starts_withstr"port="->letport'=int_of_string(String.substr5(String.lengthstr-5))inport:=Someport'|strwhenString.starts_withstr"user="->letuser'=String.substr5(String.lengthstr-5)inuser:=Someuser'|strwhenString.starts_withstr"password="->letpassword'=String.substr9(String.lengthstr-9)inpassword:=Somepassword'|strwhenString.starts_withstr"database="->letdatabase'=String.substr9(String.lengthstr-9)indatabase:=Somedatabase'|strwhenString.starts_withstr"unix_domain_socket_dir="->letsocket=String.substr23(String.lengthstr-23)inunix_domain_socket_dir:=Somesocket|strwhenString.starts_withstr"comment_src_loc="->letcomment_src_loc'=String.substr19(String.lengthstr-19)inbeginmatchcomment_src_loc'with|"yes"|"1"|"on"->comment_src_loc:=true|"no"|"0"|"off"->comment_src_loc:=false|_->loc_raiseloc(Failure"Unrecognized value for option 'comment_src_loc'")end|strwhenString.starts_withstr"show="->letshownam=String.substr5(String.lengthstr-5)inshow:=Someshownam|strwhenString.starts_withstr"load_custom_from="->lettxt=String.substr17(String.lengthstr-17)inload_custom_from:=Some((Unix.getcwd())^"/"^txt)|str->loc_raiseloc(Failure("Unknown flag: "^str)))flags;letf_execute=!f_executeinletf_nullable_results=!f_nullable_resultsinlethost=!hostinletuser=!userinletpassword=!passwordinletdatabase=!databaseinletport=!portinletunix_domain_socket_dir=!unix_domain_socket_dirinletkey=PGOCaml.describe_connection?host?user?password?database?port?unix_domain_socket_dir()inkey,f_execute,f_nullable_results,!comment_src_loc,!show,!load_custom_fromletmk_conversions?load_custom_from~loc~dbhresults=List.mapi(funi(result,nullable)->letfield_type=result.PGOCaml.field_typeinletfn=matchunravel_typedbh?load_custom_from~colnam:result.PGOCaml.namefield_typewith|nam,None->letfn=nam^"_of_string"in[%exprPGOCaml.([%eexp_of_string~locfn])][@metalocloc]|_nam,Some(_,deserialize)->exp_of_string~locdeserializeinletcol=letcname="c"^string_of_intiinExp.ident{txt=Lidentcname;loc}inletsconv=[%exprmatch[%ecol]withSomex->x|None->"-"][@metalocloc]inifnullablethen([%exprPGOCaml_aux.Option.map[%efn][%ecol]][@metalocloc]),sconvelse([%expr[%efn](tryPGOCaml_aux.Option.get[%ecol]with|_->failwith"ppx_pgsql's nullability heuristic has failed - use \"nullable-results\"")][@metalocloc]),sconv)resultsletcoretype_of_type~loc~dbhoid=lettyp=matchunravel_typedbhoidwith|"timestamp",_->Longident.Ldot(Ldot(Lident"CalendarLib","Calendar"),"t")|nam,_->Lidentnamin{ptyp_desc=Ptyp_constr({txt=typ;loc},[]);ptyp_loc=loc;ptyp_attributes=[];ptyp_loc_stack=[]}(** produce a list pattern to match the result of a query *)letmk_listpat~locresults=List.fold_right(funitail->letvar=Pat.var@@{txt="c"^string_of_inti;loc}in([%pat?[%pvar]::[%ptail]][@metalocloc]))(range0(List.lengthresults))([%pat?[]][@metalocloc])letpgsql_expand~genobject?(flags=[])locdbhquery=letopenRresultinlet(key,f_execute,f_nullable_results,comment_src_loc,show,load_custom_from)=parse_flagsflagslocinletquery=ifcomment_src_locthenletstart=loc.Location.loc_startinletopenLexingin(Printf.sprintf"-- '%s' L%d\n"start.pos_fnamestart.pos_lnum)^queryelsequeryin(* Connect, if necessary, to the database. *)get_connection~lockey>>=funmy_dbh->(* Split the query into text and variable name parts using Re.split_full.
* eg. "select id from employees where name = $name and salary > $salary"
* would become a structure equivalent to:
* ["select id from employees where name = "; "$name"; " and salary > ";
* "$salary"].
* Actually it's a wee bit more complicated than that ...
*)letsplit=letf=function|`Texttext->`Texttext|`Delimsubs->`VarRe.Group.(getsubs3,testsubs1,testsubs2)inList.mapf(Re.split_fullrexquery)in(* Go to the database, prepare this statement, and find out exactly
* what the parameter types and return values are. Exceptions can
* be raised here if the statement is bad SQL.
*)let(params,results),varmap=(* Rebuild the query with $n placeholders for each variable. *)letnext=leti=ref0infun()->incri;!iinletvarmap=Hashtbl.create8inletquery=String.concat""(List.map(function|`Texttext->text|`Var(varname,false,option)->leti=next()inHashtbl.addvarmapi(varname,false,option);Printf.sprintf"$%d"i|`Var(varname,true,option)->leti=next()inHashtbl.addvarmapi(varname,true,option);Printf.sprintf"($%d)"i)split)inletvarmap=Hashtbl.fold(funivarvars->(i,var)::vars)varmap[]intryPGOCaml.preparemy_dbh~query();PGOCaml.describe_statementmy_dbh(),varmapwithexn->loc_raiselocexnin(* If the PGSQL(dbh) "execute" flag was used, we will actually
* execute the statement now. Normally this would never be used, but
* some statements need to be executed, particularly CREATE TEMPORARY
* TABLE.
*)iff_executethenignore(PGOCaml.executemy_dbh~params:[]());(* Number of params should match length of map, otherwise something
* has gone wrong in the substitution above.
*)ifList.lengthvarmap<>List.lengthparamsthenloc_raiseloc(Failure("Mismatch in number of parameters found by database. "^"Most likely your statement contains bare $, $number, etc."));(* Generate a function for converting the parameters.
*
* See also:
* http://archives.postgresql.org/pgsql-interfaces/2006-01/msg00043.php
*)letparams=List.fold_right(fun(i,{PGOCaml.param_type=param_type})tail->letvarname,list,option=List.associvarmapinletargnam=ifString.starts_withvarname"{"thenNoneelseSomevarnameinletvarname=ifString.starts_withvarname"{"thenString.subvarname1(String.lengthvarname-2)elsevarnameinletvarname,typnam=matchString.index_optvarname':'with|None->varname,None|Some_->let[@warning"-8"][varname;typnam]=String.split_on_char':'varnameinvarname,Some(String.trimtypnam)inletvarname=exp_of_string~locvarnameinletvarname={varnamewithpexp_loc=loc}inletfn=matchunravel_type?load_custom_from?argnam?typnammy_dbhparam_typewith|nam,None->letfn=exp_of_string~loc("string_of_"^nam)in[%exprPGOCaml.([%efn])][@metalocloc]|_,Some(serialize,_)->exp_of_string~locserializeinlethead=matchlist,optionwith|false,false->[%expr[Some([%efn][%evarname])]][@metalocloc]|false,true->[%expr[PGOCaml_aux.Option.map[%efn][%evarname]]][@metalocloc]|true,false->[%exprList.map(funx->Some([%efn]x))[%evarname]][@metalocloc]|true,true->[%exprList.map(funx->PGOCaml_aux.Option.map[%efn])[%evarname]][@metalocloc]in([%expr[%ehead]::[%etail]][@metalocloc]))(List.combine(range1(1+List.lengthvarmap))params)([%expr[]][@metalocloc])in(* Substitute expression. *)letexpr=letsplit=List.fold_right(funstail->lethead=matchswith|`Texttext->([%expr`Text[%econst_string~loctext]][@metalocloc])|`Var(varname,list,option)->letlist=iflistthen([%exprtrue][@metalocloc])else([%exprfalse][@metalocloc])inletoption=ifoptionthen([%exprtrue][@metalocloc])else([%exprfalse][@metalocloc])in([%expr`Var([%econst_string~locvarname],[%elist],[%eoption])][@metalocloc])in([%expr[%ehead]::[%etail]][@metalocloc]))split([%expr[]][@metalocloc])in[%expr(* let original_query = $str:query$ in * original query string *)letdbh=[%edbh]inletparams:stringoptionlistlist=[%eparams]inletsplit=[%esplit]in(* split up query *)(* Rebuild the query with appropriate placeholders. A single list
* param can expand into several placeholders.
*)leti=ref0in(* Counts parameters. *)letj=ref0in(* Counts placeholders. *)letquery=String.concat""(List.map(function|`Texttext->text|`Var(_varname,false,_)->(* non-list item *)let()=incriin(* next parameter *)let()=incrjin(* next placeholder number *)"$"^string_of_intj.contents|`Var(_varname,true,_)->(* list item *)letparam=List.nthparamsi.contentsinlet()=incriin(* next parameter *)"("^String.concat","(List.map(fun_->let()=incrjin(* next placeholder number *)"$"^string_of_intj.contents)param)^")")split)in(* Flatten the parameters to a simple list now. *)letparams=List.flattenparamsin(* Get a unique name for this query using an MD5 digest. *)letname="ppx_pgsql."^Digest.to_hex(Digest.stringquery)in(* Get the hash table used to keep track of prepared statements. *)lethash=tryPGOCaml.private_datadbhwith|Not_found->lethash=Hashtbl.create17inPGOCaml.set_private_datadbhhash;hashin(* Have we prepared this statement already? If not, do so. *)letis_prepared=Hashtbl.memhashnameinPGOCaml.bind(ifnotis_preparedthenPGOCaml.bind(PGOCaml.preparedbh~name~query())(fun()->Hashtbl.addhashnametrue;PGOCaml.return())elsePGOCaml.return())(fun()->(* Execute the statement, returning the rows. *)PGOCaml.execute_revdbh~name~params())][@metalocloc]in(** decorate the results with the nullability heuristic *)letresults'=matchresultswith|Someresults->Some(List.map(funresult->match(result.PGOCaml.table,result.PGOCaml.column)with|Sometable,Somecolumn->(* Find out whether the column is nullable from the
* database pg_attribute table.
*)letparams=[Some(PGOCaml.string_of_oidtable);Some(PGOCaml.string_of_intcolumn)]inlet_rows=PGOCaml.executemy_dbh~name:nullable_name~params()inletnot_nullable=match_rowswith|[[Someb]]->PGOCaml.bool_of_stringb|_->falseinresult,f_nullable_results||notnot_nullable|_->result,f_nullable_results||true(* Assume it could be nullable. *))results)|None->Noneinletmkexpr~convert~list=[%exprPGOCaml.bind[%eexpr](fun_rows->PGOCaml.return(letoriginal_query=[%econst_string~locquery]inList.rev_map(funrow->matchrowwith|[%plist]->[%econvert]|_->(* This should never happen, even if the schema changes.
* Well, maybe if the user does 'SELECT *'.
*)letmsg="ppx_pgsql: internal error: "^"Incorrect number of columns returned from query: "^original_query^". Columns are: "^String.concat"; "(List.map(function|Somestr->Printf.sprintf"%S"str|None->"NULL")row)inraise(PGOCaml.Errormsg))_rows))][@metalocloc]in(* If we're expecting any result rows, then generate a function to
* convert them. Otherwise return unit. Note that we can only
* determine the nullability of results if they correspond to real
* columns in a table, otherwise the type will always be 'type option'.
*)match(genobject,results')with|true,Someresults->letlist=mk_listpat~locresultsinletfields=List.map(fun({PGOCaml.name;field_type;_},nullable)->name,coretype_of_type~loc~dbh:my_dbhfield_type,nullable)resultsinletconvert=List.fold_left2(fun(lsacc,showacc)(name,_,_)(conv,sconv)->lethd={pcf_desc=Pcf_method({txt=name;loc},Public,Cfk_concrete(Fresh,conv));pcf_loc=loc;pcf_attributes=[]}inletename=const_string~locnameinletshowacc=[%exprletfields=([%eename],[%esconv])::fieldsin[%eshowacc]][@metalocloc]in(hd::lsacc,showacc))([],[%exprList.fold_left(funbuffer(name,value)->let()=Buffer.add_stringbuffernameinlet()=Buffer.add_charbuffer':'inlet()=Buffer.add_charbuffer' 'inlet()=Buffer.add_stringbuffervalueinlet()=Buffer.add_charbuffer'\n'inbuffer)(Buffer.create16)fields|>Buffer.contents][@metalocloc])fields(mk_conversions?load_custom_from~loc~dbh:my_dbhresults)|>fun(fields,fshow)->letfshow=[%exprletfields=[]in[%efshow]][@metalocloc]inletfields=matchshowwith|Sometxt->{pcf_desc=Pcf_method({txt;loc},Public,Cfk_concrete(Fresh,fshow));pcf_loc=loc;pcf_attributes=[]}::fields|None->fieldsinExp.mk(Pexp_object({pcstr_self=Pat.any~loc();pcstr_fields=fields}))inletexpr=mkexpr~convert~listinOkexpr|true,None->Error("It doesn't make sense to make an object to encapsulate results that aren't coming",loc)|false,Someresults->letlist=mk_listpat~locresultsinletconvert=letconversions=mk_conversions?load_custom_from~loc~dbh:my_dbhresults|>List.mapfstin(* Avoid generating a single-element tuple. *)matchconversionswith|[]->[%expr()][@metalocloc]|[a]->a|conversions->Exp.tupleconversionsinOk(mkexpr~convert~list)|false,None->Ok([%exprPGOCaml.bind[%eexpr](fun_rows->PGOCaml.return())][@metalocloc])letexpand_sql~genobjectlocdbhextras=letquery,flags=matchList.revextraswith|[]->assertfalse|query::flags->query,flagsintrypgsql_expand~genobject~flagslocdbhquerywith|Failures->Error(s,loc)|PGOCaml.Errors->Error(s,loc)|PGOCaml.PostgreSQL_Error(s,fields)->letfields'=List.map(fun(c,s)->Printf.sprintf"(%c: %s)"cs)fieldsinError("Postgres backend error: "^s^": "^s^String.concat","fields',loc)|exn->Error("Unexpected PG'OCaml PPX error: "^Printexc.to_stringexn,loc)(* Returns the empty list if one of the elements is not a string constant *)letlist_of_string_argsargs=letmaybe_strs=List.map(function|(Nolabel,{pexp_desc=Pexp_constant(Pconst_string(str,_,None));_})->Somestr|_->None)argsinifList.memNonemaybe_strsthen[]elseList.map(functionSomex->x|None->assertfalse)maybe_strsletgen_expandgenobject~loc~path:_expr=matchexprwith|{pexp_desc=Pexp_apply(dbh,args);pexp_loc=qloc;_}->beginmatchlist_of_string_argsargswith|[]->Location.raise_errorf~loc"Something unsupported"|args->beginmatchexpand_sql~genobjectlocdbhargswith|Okpexp->{pexpwithpexp_loc=qloc}|Error(s,loc)->Location.raise_errorf~loc"PG'OCaml PPX error: %s"sendend|_->Location.raise_errorf~loc"Something unsupported"letextension_pgsql=Extension.declare"pgsql"Extension.Context.expressionAst_pattern.(single_expr_payload__)(gen_expandfalse)letextension_pgsql_object=Extension.declare"pgsql.object"Extension.Context.expressionAst_pattern.(single_expr_payload__)(gen_expandtrue)letrule_pgsql=Context_free.Rule.extensionextension_pgsqlletrule_pgsql_object=Context_free.Rule.extensionextension_pgsql_objectlet()=Driver.register_transformation"pgocaml"~rules:[rule_pgsql;rule_pgsql_object]