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
    { EditRowView -> [Text]
tableNames :: [Text]
    , EditRowView -> Text
tableName :: Text
    , EditRowView -> [[DynamicField]]
rows :: [[DynamicField]]
    , EditRowView -> [ColumnDefinition]
tableCols :: [ColumnDefinition]
    , EditRowView -> [DynamicField]
rowValues :: [DynamicField]
    , EditRowView -> [Text]
primaryKeyFields :: [Text]
    , EditRowView -> Text
targetPrimaryKey :: Text
    }

instance View EditRowView where
    html :: (?context::ControllerContext, ?view::EditRowView) =>
EditRowView -> Html
html EditRowView { [[DynamicField]]
[Text]
[ColumnDefinition]
[DynamicField]
Text
$sel:tableNames:EditRowView :: EditRowView -> [Text]
$sel:tableName:EditRowView :: EditRowView -> Text
$sel:rows:EditRowView :: EditRowView -> [[DynamicField]]
$sel:tableCols:EditRowView :: EditRowView -> [ColumnDefinition]
$sel:rowValues:EditRowView :: EditRowView -> [DynamicField]
$sel:primaryKeyFields:EditRowView :: EditRowView -> [Text]
$sel:targetPrimaryKey:EditRowView :: EditRowView -> Text
tableNames :: [Text]
tableName :: Text
rows :: [[DynamicField]]
tableCols :: [ColumnDefinition]
rowValues :: [DynamicField]
primaryKeyFields :: [Text]
targetPrimaryKey :: Text
.. } = [hsx|
        <div class="h-100">
            {headerNav}
            <div class="h-100 row no-gutters">
                {renderTableSelector tableNames tableName}
                <div class="col" style="overflow: scroll; max-height: 80vh">
                    {renderRows rows tableBody tableName}
                </div>
            </div>
        </div>
        {renderModal modal}
    |]
        where
            tableBody :: Html
tableBody = [hsx|<tbody>{forEach rows renderRow}</tbody>|]
            renderRow :: [DynamicField] -> Html
renderRow [DynamicField]
fields = [hsx|<tr>{forEach fields (renderField id)}</tr>|]
                where
                    id :: Text
id = (ByteString -> Text
forall a b. ConvertibleStrings a b => a -> b
cs (ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
"" ((Maybe DynamicField -> DynamicField
forall a. HasCallStack => Maybe a -> a
fromJust ([DynamicField] -> Maybe DynamicField
forall a. [a] -> Maybe a
headMay [DynamicField]
fields)).fieldValue)))
            renderField :: Text -> DynamicField -> Html
renderField Text
id DynamicField { Maybe ByteString
ByteString
fieldValue :: Maybe ByteString
fieldName :: ByteString
$sel:fieldValue:DynamicField :: DynamicField -> Maybe ByteString
$sel:fieldName:DynamicField :: DynamicField -> ByteString
.. } | ByteString
fieldName ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
"id" = [hsx|<td><span data-fieldname={fieldName}><a class="no-link border rounded p-1" href={EditRowValueAction tableName (cs fieldName) id}>{renderId (sqlValueToText fieldValue)}</a></span></td>|]
            renderField Text
id DynamicField { Maybe ByteString
ByteString
$sel:fieldValue:DynamicField :: DynamicField -> Maybe ByteString
$sel:fieldName:DynamicField :: DynamicField -> ByteString
fieldValue :: Maybe ByteString
fieldName :: ByteString
.. } | ByteString -> [ColumnDefinition] -> Bool
forall {t :: * -> *} {a1} {a2} {a3} {r}.
(Foldable t, ConvertibleStrings a1 a2, Eq a2, Eq a3,
 HasField "columnName" r a2, HasField "columnType" r a3,
 IsString a3) =>
a1 -> t r -> Bool
isBoolField ByteString
fieldName [ColumnDefinition]
tableCols Bool -> Bool -> Bool
&& Bool -> Bool
not (Maybe ByteString -> Bool
forall a. Maybe a -> Bool
isNothing Maybe ByteString
fieldValue) = [hsx|<td><span data-fieldname={fieldName}><input type="checkbox" onclick={onClick tableName fieldName id} checked={sqlValueToText fieldValue == "t"} /></span></td>|]
            renderField Text
id DynamicField { Maybe ByteString
ByteString
$sel:fieldValue:DynamicField :: DynamicField -> Maybe ByteString
$sel:fieldName:DynamicField :: DynamicField -> ByteString
fieldValue :: Maybe ByteString
fieldName :: ByteString
.. } = [hsx|<td><span data-fieldname={fieldName}><a class="no-link" href={EditRowValueAction tableName (cs fieldName) id}>{sqlValueToText fieldValue}</a></span></td>|]


            modalContent :: Html
modalContent = [hsx|
                <form method="POST" action={UpdateRowAction}>
                    <input type="hidden" name="tableName" value={tableName}/>
                    {forEach (zip tableCols rowValues) renderFormField}
                    {forEach (zip primaryKeyFields (T.splitOn "---" targetPrimaryKey)) renderPrimaryKeyInput}
                    <div class="text-right">
                        <button type="submit" class="btn btn-primary">Edit Row</button>
                    </div>
                </form>
            |]
            modalFooter :: Maybe Html
modalFooter = Maybe Html
forall a. Monoid a => a
mempty
            modalCloseUrl :: Text
modalCloseUrl = DataController -> Text
forall controller. HasPath controller => controller -> Text
pathTo ShowTableRowsAction { Text
tableName :: Text
$sel:tableName:ShowDatabaseAction :: Text
tableName }
            modalTitle :: Text
modalTitle = Text
"Edit Row"
            modal :: Modal
modal = Modal { Html
modalContent :: Html
$sel:modalContent:Modal :: Html
modalContent, Maybe Html
modalFooter :: Maybe Html
$sel:modalFooter:Modal :: Maybe Html
modalFooter, Text
modalCloseUrl :: Text
$sel:modalCloseUrl:Modal :: Text
modalCloseUrl, Text
modalTitle :: Text
$sel:modalTitle:Modal :: Text
modalTitle }

            renderPrimaryKeyInput :: (value, value) -> Html
renderPrimaryKeyInput (value
primaryKeyField, value
primaryKeyValue) = [hsx|<input type="hidden" name={primaryKeyField <> "-pk"} value={primaryKeyValue}>|]
            
            renderFormField :: (ColumnDefinition, DynamicField) -> Html
            renderFormField :: (ColumnDefinition, DynamicField)
-> (?context::ControllerContext) => Html
renderFormField (ColumnDefinition
def, DynamicField
val) = [hsx|
                    <div class="form-group">
                        <label class="row-form">{def.columnName}</label>
                        <span style="float:right;">
                            <a class="text-muted row-form">{def.columnType}</a>
                        </span>

                        <div class="input-group">
                            {renderInputMethod (def, val)}
                        </div>
                    </div>|]

            onClick :: Text -> a -> Text -> Text
onClick Text
tableName a
fieldName Text
id = Text
"window.location.assign(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
forall a. Show a => a -> Text
tshow (DataController -> Text
forall controller. HasPath controller => controller -> Text
pathTo (Text -> Text -> Text -> DataController
ToggleBooleanFieldAction Text
tableName (a -> Text
forall a b. ConvertibleStrings a b => a -> b
cs a
fieldName) Text
id)) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
            renderInputMethod :: (ColumnDefinition, DynamicField) -> Html
            renderInputMethod :: (ColumnDefinition, DynamicField)
-> (?context::ControllerContext) => Html
renderInputMethod (ColumnDefinition
def, DynamicField
val) | (ColumnDefinition
def.columnType) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"boolean" Bool -> Bool -> Bool
&& Maybe ByteString -> Bool
forall a. Maybe a -> Bool
isNothing (DynamicField
val.fieldValue) = [hsx|
                            {isBooleanParam True def}
                            <input
                                id={def.columnName <> "-alt"}
                                type="text"
                                name={def.columnName}
                                class="form-control text-monospace text-secondary bg-light"
                                value="NULL"
                                />
                            <div class="form-control" id={def.columnName <> "-boxcontainer"}>
                                <input
                                    id={def.columnName <> "-input"}
                                    type="checkbox"
                                    class="d-none"
                                    name={def.columnName <> "-inactive"}
                                    checked={(value val) == "t"}
                                    />
                            </div>
                            <input
                                id={def.columnName <> "-hidden"}
                                type="hidden"
                                name={def.columnName}
                                value={inputValue False}
                                />
                            <div class="input-group-append">
                                <button class="btn dropdown-toggle" type="button" data-toggle="dropdown" aria-haspopup="true" aria-expanded="false"></button>
                                <div class="dropdown-menu dropdown-menu-right custom-menu menu-for-column shadow backdrop-blur">
                                    <a class="dropdown-item" data-value="DEFAULT" data-issql="True" onclick={fillField def "DEFAULT" "true"}>DEFAULT</a>
                                    <a class="dropdown-item" data-value="NULL" data-issql="True" onclick={fillField def "NULL" "true"}>NULL</a>
                                    <a class="dropdown-item">
                                        <input
                                            id={def.columnName <> "-sqlbox"}
                                            type="checkbox"
                                            name={def.columnName <> "_"}
                                            checked={True}
                                            class="mr-1"
                                            onclick={"sqlModeCheckbox('" <> def.columnName <> "', this, true)"}
                                            />
                                        <label class="form-check-label" for={def.columnName <> "-sqlbox"}> Parse as SQL</label>
                                    </a>
                                    <input
                                        type="hidden"
                                        name={def.columnName <> "_"}
                                        value={inputValue False}
                                        />
                                </div>
                            </div>
                                |]
            renderInputMethod (ColumnDefinition
def, DynamicField
val) | (ColumnDefinition
def.columnType) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"boolean" = [hsx|
                            {isBooleanParam True def}
                            <input
                                id={def.columnName <> "-alt"}
                                type="text"
                                name={def.columnName <> "-inactive"}
                                class="form-control text-monospace text-secondary bg-light d-none"
                                />
                            <div class="form-control" id={def.columnName <> "-boxcontainer"}>
                                <input
                                    id={def.columnName <> "-input"}
                                    type="checkbox"
                                    name={def.columnName}
                                    checked={(value val) == "t"}
                                    />
                            </div>
                            <input
                                id={def.columnName <> "-hidden"}
                                type="hidden"
                                name={def.columnName}
                                value={inputValue False}
                                />
                            <div class="input-group-append">
                                <button class="btn dropdown-toggle" type="button" data-toggle="dropdown" aria-haspopup="true" aria-expanded="false"></button>
                                <div class="dropdown-menu dropdown-menu-right custom-menu menu-for-column shadow backdrop-blur">
                                    <a class="dropdown-item" data-value="DEFAULT" data-issql="True" onclick={fillField def "DEFAULT" "true"}>DEFAULT</a>
                                    <a class="dropdown-item" data-value="NULL" data-issql="True" onclick={fillField def "NULL" "true"}>NULL</a>
                                    <a class="dropdown-item">
                                        <input
                                            id={def.columnName <> "-sqlbox"}
                                            type="checkbox"
                                            name={def.columnName <> "_"}
                                            checked={isSqlFunction (getColDefaultValue def)}
                                            class="mr-1"
                                            onclick={"sqlModeCheckbox('" <> def.columnName <> "', this, true)"}
                                            />
                                        <label class="form-check-label" for={def.columnName <> "-sqlbox"}> Parse as SQL</label>
                                    </a>
                                    <input
                                        type="hidden"
                                        name={def.columnName <> "_"}
                                        value={inputValue False}
                                        />
                                </div>
                            </div>
                                |]
            renderInputMethod (ColumnDefinition
def, DynamicField
val) = [hsx|
                            {isBooleanParam False def}
                            <input
                                id={def.columnName <> "-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 <> "')"}
                                />
                            <div class="input-group-append">
                                <button class="btn dropdown-toggle" type="button" data-toggle="dropdown" aria-haspopup="true" aria-expanded="false"></button>
                                <div class="dropdown-menu dropdown-menu-right custom-menu menu-for-column shadow backdrop-blur">
                                    <a class="dropdown-item" data-value="DEFAULT" data-issql="True" onclick={fillField def "DEFAULT" "false"}>DEFAULT</a>
                                    <a class="dropdown-item" data-value="NULL" data-issql="True" onclick={fillField def "NULL" "false"}>NULL</a>
                                    <a class="dropdown-item">
                                        <input
                                            id={def.columnName <> "-sqlbox"}
                                            type="checkbox"
                                            name={def.columnName <> "_"}
                                            checked={isSqlFunction_ (value val)}
                                            class="mr-1"
                                            onclick={"sqlModeCheckbox('" <> def.columnName <> "', this)"}
                                            />
                                        <label class="form-check-label" for={def.columnName <> "-sqlbox"}> Parse as SQL</label>
                                    </a>
                                    <input
                                        type="hidden"
                                        name={def.columnName <> "_"}
                                        value={inputValue False}
                                        />
                                </div>
                            </div>|]

value :: r -> ByteString
value r
val = ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
BS.empty (r
val.fieldValue)