[Haskell-cafe] re: Oracle stored procedures
Leonel Fonseca
leonelfl at gmail.com
Thu Sep 9 01:13:18 EDT 2010
Hi Peter,
Yes, from Takusen you can call Oracle stored procedures, functions,
packaged stored procedures or functions, or execute an arbitrary
pl/sql block.
In the Takusen software release there is a directory called
"Database\Oracle\Test". There, Enumerator.lhs, among other code has
these helpers you may want to use:
>wrapPLSQLFunc funcname parms =
> let sqltext = "begin " ++ (head args) ++ " := " ++ funcname
> ++ "(" ++ placeholders ++ "); end;"
> placeholders = concat (intersperse "," (tail args))
> args = take (length parms) (map (\n -> ":x" ++ show n) [1..])
> in cmdbind sqltext parms
>wrapPLSQLProc procname parms =
> let sqltext = "begin " ++ procname
> ++ "(" ++ placeholders ++ "); end;"
> placeholders = concat (intersperse "," args)
> args = take (length parms) (map (\n -> ":x" ++ show n) [1..])
> in cmdbind sqltext parms
Please, be aware of the following points:
1) If the pl/sql code doesn't need parameters and has no results, you
can use "execDDL". (execDML returns a counter of affected rows).
2) If the procedure/function receives parameter, you'll need to use
"cmdbind" (or similar to "cmdbind") to pass the parameters.
3) If the pl/sql code returns values, you have this options:
3.a) The returned value is a reference (cursor): Takusen supports
this very fine. Use "doQuery" or similar.
3.b) The return value is an scalar value: You can collect the
result with an iteratee, even if it is a single value.
3.c) The return value is a complex oracle object: As of Takusen
0.8.5 there is no support for table of records of ...
3.d) The return value is Boolean. You'll get an error.
Little examples:
For case #1:
> -- Example 1.a: We set nls_language to american english.
> set_NlsLang_Eng :: DBM mark Session ()
> set_NlsLang_Eng = execDDL $ sql
> "alter session set nls_language='AMERICAN'"
> -- Example #1.b: Now we set session language parameter to spanish.
> set_NlsLang_Esp :: DBM mark Session ()
> set_NlsLang_Esp = execDDL $ sql
> "alter session set nls_language='LATIN AMERICAN SPANISH'"
For case #2:
> -- Example 2.a: We use database string "concat" function
>concat' :: String -> String -> DBM mark Session String
>concat' a b = do
> let ite :: Monad m => String -> IterAct m String
> ite v _ = return $ Left v
> sqlcmd = wrapPLSQLFunc "concat"
> [bindP $ Out (""::String), bindP a, bindP b]
> doQuery sqlcmd ite undefined
>
> -- later on the program, you'd have...
> some_string <- concat' "a" "b"
For case #3:
> -- Case 3.b: We collect a single scalar value.
> qNlsLang :: DBM mark Session [String]
> qNlsLang = doQuery s ite []
> where
> s = "select value from nls_session_parameters \
> \ where parameter = 'NLS_LANGUAGE'"
> ite :: (Monad m) => String -> IterAct m [String]
> ite a acc = result' ( a:acc )
> mostrar_NlsLang :: DBM mark Session ()
> mostrar_NlsLang = qNlsLang >>= liftIO . print . head
> -- Another example for Case 3.b
> -- This time we don't use a list to accumulate results.
> s1 = sql "select systimestamp from dual"
>
> sysTSasCTQ :: DBM mark Session CalendarTime
> sysTSasCTQ = do
>
> let ite :: (Monad m) => CalendarTime -> IterAct m CalendarTime
> ite x _ = result' x
>
> t <- liftIO ( getClockTime >>= toCalendarTime)
> doQuery s1 ite t
--
Leonel Fonseca.
More information about the Haskell-Cafe
mailing list