Example $\#$01 of Tránsito Abierto. \medskip Leonel Fonseca. 2010/09/15. \medskip A simple query. \medskip You may compile this program with \verb|ghc --make Ex01|. \medskip \begin{code} {-# options -fglasgow-exts #-} {-# language TemplateHaskell #-} module Main where import Database.TA.TAB import RCSdef \end{code} We import ``RCSdef'' which provides ``rcs01'', a list of DBM actions that can generate database access code. Each of these DBM actions acts as an AST builder, that when evaluated generates code for two definitions: \begin{enumerate} \item A record type that would define the type of the query result. \item An action of type DBM (from Takusen) that would contain an iteratee function and would perform the parameter binding (if provided), the query and the fetch (accumulation) of results. \end{enumerate} \begin{code} empalmar "abel" "cain" "barva" Nothing rcs01 \end{code} \bigskip This is the second step in cutting boilerplate. By issuing ``empalmar'', ``rcs01'' is evaluated in the DBM monad, and its results are generated code to be spliced. If we were to consider ``rcs01'' a seed, passing it to ``empalmar'' is akin to planting the seed and making it germinate. New code would spring. \bigskip ``empalmar'' needs a database connection in order to infer the type of the result and the Takusen DBM action which will do the query. In this example, we used these three values to represent the database connection: ``abel'' as the database account; its password, ``cain''; and the database service, ``barva''. \bigskip We will defer the discussion of what is the ``Nothing'' value in this call to another example. \bigskip \begin{code} main :: IO () main = do r <- withSession (connect "abel" "cain" "barva") ( qTwoColumns [[]] ) mapM_ (putStrLn . show) $ concat r \end{code} \bigskip A fact that may attract reader's attention it is that ``qTwoColumns'' may have binded values as parameters. In this example, no parameters are use, hence we passed an empty list --of lists--. \bigskip Three names came along from the module ``RCSdef'': \begin{enumerate} \item ``rcs01'': this a list of DBM actions. When evaluated builds a list of AST's of Haskell code that provide definitions of query types and query functions. It is defined by the programmer by calling functions and constructors of the Tránsito Abierto library. \item ``qTwoColumns'': It is, too, a DBM action that performs the query and accumulates the results. It has its own iteratee function. The name ``qTwoColumns'' was selected by the programmer in the module ``RCSdef'' by means of the call to ``genSelect''. \item ``QTwoColumns'': is a name selected and defined by the Tránsito Abierto library's code generator. It is a record type for describing the results of the query ``qTwoColumns''. \end{enumerate} \bigskip Both ``qTwoColumns'' and ``QTwoColumns'' are injected to GHC compiler's structures when this module (``Ex01.lhs'') is compiled. Exactly, they are known in the scope of this program when the action ``empalmar'' is evaluated, because it splices the code built by computing ``rcs01''. \bigskip ``rcs01'' can be thought as an immutable seed. Its generative properties can be used serveral times to generate code that is dependent of the database environment. \bigskip Given that the names for the columns of the table ``twoColumns'' are these: \begin{Verbatim}[frame=lines] SQL> desc twoColumns Name Null? Type ----------------------------------------- -------- -------------- NAME VARCHAR2(20) VALUE NUMBER(5) \end{Verbatim} the user of the library would expect that the fields of the record follow similar names. \bigskip