module IHP.IDE.SchemaDesigner.View.Schema.SchemaUpdateFailed where import IHP.ViewPrelude import IHP.IDE.ToolServer.Types import IHP.IDE.ToolServer.Routes () import System.Exit import qualified Data.Text as Text data SchemaUpdateFailedView = SchemaUpdateFailedView { output :: Text , exitCode :: ExitCode } instance View SchemaUpdateFailedView where html SchemaUpdateFailedView { .. } = renderModal Modal { modalTitle = "Open your Fixtures.sql and apply required changes to fix this error. After that try again." , modalCloseUrl = pathTo TablesAction , modalFooter = Nothing , modalContent = [hsx|
{forEach errorMessages renderError} {outputLines |> map renderLine |> mconcat}
|] } where -- | E.g. the make db succeeded but there an sql error inside the output isSqlError = exitCode == ExitSuccess outputLines :: [Text] outputLines = Text.lines output errorMessages :: [Text] errorMessages = zip [0..] outputLines |> filter (\(i, line) -> "ERROR" `Text.isInfixOf` line) |> map (\(i, line) -> let nextLine :: Text = if i < length outputLines then outputLines !! (i + 1) else "" in if "DETAIL" `isPrefixOf` nextLine then (i, line <> "\n" <> nextLine) else (i, line) ) |> map snd renderError message = [hsx|
{nl2br message}
|] renderLine :: Text -> Html renderLine line = [hsx|
{line}
|]