module IHP.IDE.Data.View.Layout
( customQuery
, tableHead
, renderRows
, sqlValueToText
, renderId
, isBoolField
, isSqlFunction
, isSqlFunction_
, fillField
, getColDefaultValue
, renderRowValue
, renderDefaultWithoutType
, isBooleanParam
, headerNav
) where
import IHP.ViewPrelude
import IHP.IDE.ToolServer.Types
import IHP.IDE.ToolServer.Routes ()
import qualified Data.Text as Text
import IHP.IDE.ToolServer.Helper.View
customQuery :: Text -> Html
customQuery input = [hsx|
|]
tableHead :: [[DynamicField]] -> Text -> Html
tableHead rows tableName =
[hsx|
{forEach (columnNames rows) renderColumnHead}
|
|]
where
columnNames rows = map (.fieldName) (fromMaybe [] (head rows))
renderColumnHead name = [hsx|{name} | |]
renderRows :: [[DynamicField]] -> Html -> Text -> Html
renderRows rows body tableName = [hsx|
{tableHead rows tableName}
{body}
|]
sqlValueToText :: Maybe ByteString -> Text
sqlValueToText (Just value) = cs value
sqlValueToText Nothing = "NULL"
renderId id = take 4 (cs id) <> ".." <> reverse (take 4 (reverse (cs id)))
isBoolField fieldName tableCols = case (find (\c -> c.columnName == (cs fieldName)) tableCols) of
Just columnDef -> (columnDef.columnType) == "boolean"
Nothing -> False
isSqlFunction :: Text -> Bool
isSqlFunction text = text `elem`
[ "uuid_generate_v4()"
, "NOW()"
, "NULL"]
isSqlFunction_ :: ByteString -> Bool
isSqlFunction_ text = text `elem`
[ "uuid_generate_v4()"
, "NOW()"
, "NULL"]
fillField col value isBoolField = "fillField('" <> col.columnName <> "', '" <> value <> "'," <> isBoolField <> ");"
getColDefaultValue :: ColumnDefinition -> Text
getColDefaultValue ColumnDefinition { columnDefault, isNullable } = case columnDefault of
Just value -> value
Nothing -> if isNullable
then "NULL"
else ""
renderRowValue :: Maybe ByteString -> Text
renderRowValue (Just value) = "'" <> cs value <> "'"
renderRowValue Nothing = "NULL"
renderDefaultWithoutType :: Text -> Text
renderDefaultWithoutType "" = ""
renderDefaultWithoutType input = case length (Text.splitOn "'" input) of
3 -> (Text.splitOn "'" input) !! 1
_ -> input
isBooleanParam :: Bool -> ColumnDefinition -> Html
isBooleanParam isBool def = [hsx|
"-isBoolean"}
value={inputValue isBool}
/>
|]
headerNav :: Html
headerNav = [hsx|
|]
where
databaseActive :: Bool
databaseActive = isActiveController @DataController && not sqlActive
sqlActive :: Bool
sqlActive = isActivePath NewQueryAction || isActivePath QueryAction