module IHP.IDE.SchemaDesigner.View.Migrations.Index where import IHP.ViewPrelude import IHP.IDE.ToolServer.Helper.View import IHP.SchemaMigration import IHP.IDE.ToolServer.Types import IHP.IDE.ToolServer.Routes () import qualified Data.Time.Clock.POSIX as Clock type Revision = Int data IndexView = IndexView { migrationsWithSql :: ![(Migration, Text)] , migratedRevisions :: ![Int] , lastError :: !(Maybe Text) } instance View IndexView where html IndexView { migrationsWithSql = [] } = emptyState html IndexView { .. } = [hsx|
{addIcon}
{renderFlashMessages}
{forEachWithIndex migrationsWithSql renderMigration}
{migrationsContextMenu} |] where renderMigration :: (Int, (Migration, Text)) -> Html renderMigration (index, (migration, sqlStatements)) = [hsx|
contextMenuId <> "'); event.stopPropagation();"}>
{runOrStatus} {when pending editAndDelete}
{code "sql" sqlStatements}
{migrationContextMenu migration contextMenuId pending} |] where pending = (migration.revision) `notElem` migratedRevisions currentError = lastError contextMenuId :: Text contextMenuId = "context-menu-migration-" <> tshow (migration.revision) editAndDelete = [hsx|
{editIcon} {deleteIcon}
|] currentErrorHtml = unless (isNothing currentError) [hsx|
{currentError}
|] runOrStatus :: Html runOrStatus = if pending then [hsx|
{currentErrorHtml}
|] else [hsx|
{timeAgo revisionTime} {checkmark}
|] revisionTime :: UTCTime revisionTime = Clock.posixSecondsToUTCTime $ (fromInteger (fromIntegral (migration.revision))) code :: Text -> Text -> Html code _ src = [hsx|
{src}
|] checkmark = preEscapedToHtml [plain| |] emptyState :: Html emptyState = [hsx|

No Migration yet.

+ New Migration

{migrationsContextMenu} |] migrationsContextMenu :: Html migrationsContextMenu = [hsx| |] migrationContextMenu migration contextMenuId pending = [hsx| |] where migrationId :: Int migrationId = migration.revision currentMigrationActions = when pending [hsx| Edit Migration Delete Migration
|]