module IHP.IDE.Data.View.EditRow where import IHP.ViewPrelude import IHP.IDE.ToolServer.Types import IHP.IDE.Data.View.ShowDatabase import IHP.IDE.Data.View.Layout import Data.Maybe import qualified Data.Text as T import qualified Data.ByteString as BS data EditRowView = EditRowView { tableNames :: [Text] , tableName :: Text , rows :: [[DynamicField]] , tableCols :: [ColumnDefinition] , rowValues :: [DynamicField] , primaryKeyFields :: [Text] , targetPrimaryKey :: Text } instance View EditRowView where html EditRowView { .. } = [hsx|
{headerNav}
{renderTableSelector tableNames tableName}
{renderRows rows tableBody tableName}
{renderModal modal} |] where tableBody = [hsx|{forEach rows renderRow}|] renderRow fields = [hsx|{forEach fields (renderField id)}|] where id = (cs (fromMaybe "" ((fromJust (headMay fields)).fieldValue))) renderField id DynamicField { .. } | fieldName == "id" = [hsx|{renderId (sqlValueToText fieldValue)}|] renderField id DynamicField { .. } | isBoolField fieldName tableCols && not (isNothing fieldValue) = [hsx||] renderField id DynamicField { .. } = [hsx|{sqlValueToText fieldValue}|] modalContent = [hsx|
{forEach (zip tableCols rowValues) renderFormField} {forEach (zip primaryKeyFields (T.splitOn "---" targetPrimaryKey)) renderPrimaryKeyInput}
|] modalFooter = mempty modalCloseUrl = pathTo ShowTableRowsAction { tableName } modalTitle = "Edit Row" modal = Modal { modalContent, modalFooter, modalCloseUrl, modalTitle } renderPrimaryKeyInput (primaryKeyField, primaryKeyValue) = [hsx| "-pk"} value={primaryKeyValue}>|] renderFormField :: (ColumnDefinition, DynamicField) -> Html renderFormField (def, val) = [hsx|
{def.columnType}
{renderInputMethod (def, val)}
|] onClick tableName fieldName id = "window.location.assign(" <> tshow (pathTo (ToggleBooleanFieldAction tableName (cs fieldName) id)) <> ")" renderInputMethod :: (ColumnDefinition, DynamicField) -> Html renderInputMethod (def, val) | (def.columnType) == "boolean" && isNothing (val.fieldValue) = [hsx| {isBooleanParam True def} "-alt"} type="text" name={def.columnName} class="form-control text-monospace text-secondary bg-light" value="NULL" />
"-boxcontainer"}> "-input"} type="checkbox" class="d-none" name={def.columnName <> "-inactive"} checked={(value val) == "t"} />
"-hidden"} type="hidden" name={def.columnName} value={inputValue False} />
|] renderInputMethod (def, val) | (def.columnType) == "boolean" = [hsx| {isBooleanParam True def} "-alt"} type="text" name={def.columnName <> "-inactive"} class="form-control text-monospace text-secondary bg-light d-none" />
"-boxcontainer"}> "-input"} type="checkbox" name={def.columnName} checked={(value val) == "t"} />
"-hidden"} type="hidden" name={def.columnName} value={inputValue False} />
|] renderInputMethod (def, val) = [hsx| {isBooleanParam False def} "-input"} type="text" name={def.columnName} class={classes ["form-control", ("text-monospace text-secondary bg-light", isSqlFunction_ (value val))]} value={value val} oninput={"stopSqlModeOnInput('" <> def.columnName <> "')"} />
|] value val = fromMaybe BS.empty (val.fieldValue)