module Database.YamSql.Internal.Obj.Function where
import Database.YamSql.Internal.Basic
import Database.YamSql.Internal.Commons
data Function = Function
{ functionName :: SqlName
, functionDescription :: Text
, functionReturns :: SqlType
, functionParameters :: Maybe [Variable]
, functionTemplates :: Maybe [SqlName]
, functionTemplateData :: Maybe [FunctionTpl]
, functionReturnsColumns :: Maybe [Parameter]
, functionVariables :: Maybe [Variable]
, functionPrivExecute :: Maybe [SqlName]
, functionSecurityDefiner :: Maybe Bool
, functionOwner :: Maybe SqlName
, functionLanguage :: Maybe Text
, functionBody :: Maybe Text
} deriving (Generic, Show, Data)
instance FromJSON Function where
parseJSON = parseYamSql
instance ToJSON Function where
toJSON = toYamSqlJson
data SQL_FUNCTION =
SQL_FUNCTION
deriving (SqlObjType, Show)
instance ToSqlCode SQL_FUNCTION where
toSqlCode = const "FUNCTION"
data FunctionTpl = FunctionTpl
{ functiontplTemplate :: SqlName
, functiontplDescription :: Text
, functiontplLanguage :: Maybe Text
, functiontplParameters :: Maybe [Variable]
, functiontplVariables :: Maybe [Variable]
, functiontplPrivExecute :: Maybe [SqlName]
, functiontplSecurityDefiner :: Maybe Bool
, functiontplOwner :: Maybe SqlName
, functiontplBodyPrelude :: Maybe Text
, functiontplBodyPostlude :: Maybe Text
} deriving (Generic, Show, Data)
instance FromJSON FunctionTpl where
parseJSON = parseYamSql
instance ToJSON FunctionTpl where
toJSON = toYamSqlJson
applyFunctionTpl :: FunctionTpl -> Function -> Function
applyFunctionTpl t f =
f
{ functionPrivExecute =
maybeRight (functiontplPrivExecute t) (functionPrivExecute f)
, functionSecurityDefiner =
maybeRight (functiontplSecurityDefiner t) (functionSecurityDefiner f)
, functionOwner = maybeRight (functiontplOwner t) (functionOwner f)
, functionParameters =
maybeJoin (functionParameters f) (functiontplParameters t)
, functionVariables = maybeJoin (functionVariables f) (functiontplVariables t)
, functionBody =
Just $
maybeStringL (functiontplBodyPrelude t) <> fromMaybe "" (functionBody f) <>
maybeStringR (functiontplBodyPostlude t)
}
where
maybeStringL (Just xs) = xs <> "\n"
maybeStringL Nothing = ""
maybeStringR (Just xs) = "\n" <> xs
maybeStringR Nothing = ""