Example $\#$02 of TrĂ¡nsito Abierto. Leonel Fonseca. 2010/09/16. \medskip A ``wear the safety belt'' style of program. We ask the code generator to save the database access generated code in a variable named ``oldCode'', this happens at compile time. Later, when the program is executed we ask the code generator for a fresh instance of code. Then we compare ``oldCode'' against the new code. If they don't match it means your database environment has changed and it's not safe to execute the program. \bigskip You may compile this program with \verb|ghc --make Ex02|. This example reuses the definitions in ``RCSdef'', but it is independent from the example $\#$01. \begin{code} {-# options -fglasgow-exts #-} {-# language TemplateHaskell #-} module Main where import Database.TA.TAB import Control.Monad ( when ) import System ( ExitCode (..), exitWith ) import RCSdef \end{code} We import ``Database.TA.TAB'' which provides the code generator and utilities. The import of ``RCSdef'' brings into scope the name ``rcs01'', a list of AST builders (or DBM actions that when evaluated will yield an AST representation of code, whose type is \verb|Q [Dec]|). \begin{code} empalmar "abel" "cain" "barva" (Just "oldCode") rcs01 \end{code} In the example $\#01$ you will find an explanation for most of the parameters of ``empalmar''. We now explain \verb|(Just "oldCode")|. The type of this parameter is \verb|Maybe String|. This parameter directs the following processing: \begin{itemize} \item When given \verb|Nothing|, the code generated has two declarations: one for a datatype and one for DBM action for database access. \item When given \verb|(Just "someIdentifierName")|, besides the two cited declarations, a third declaration is elaborated: The name ``someIdentifierName'' is binded with the value of the former two declarations. In other words, a snapshot of the ASTs (of the datatype and the DBM action) is made. \end{itemize} In this particular case, ``rcs01'' has the potential to generate access code and ``oldCode'' has an instance of the code generated at compile time. \begin{code} main :: IO () main = do ((stop,_,_), s) <- withContinuedSession (connect "abel" "cain" "barva") (ambBDCompatible oldCode rcs01) when stop ( do putStrLn stopMessage _ <- withSession s $ return () exitWith (ExitFailure 1) ) r <- withSession s ( qTwoColumns [[]] ) mapM_ (putStrLn . show) $ concat r \end{code} ``ambBDCompatible'' returns a triple. The first value is a boolean value. If both, the old generated (at compile time) code and the new generated code (obtained from evaluating ``rcs01''), are equal the result is true, otherwise false. The second and third values are, respectively, the list of old declarations and the list of new declarations. In this example, we chose to save the returned comparison value for interrogating it later. So, in the case this program is not safe to run due database changes that result in different generated code, it will warn you and stop. \begin{code} stopMessage = "Error: The database environment has changed!\n" ++ " It doesn't match the enviroment this program expects. \n" ++ " As a measure to avoid further errors, this program will finish now." \end{code}