restart on upgrade is working, including automatic restart

Made alerts be able to have multiple buttons, so the alerts about upgrading
can have a button that enables automatic upgrades.

Implemented automatic upgrading when the program file has changed.

Note that when an automatic upgrade happens, the webapp displays an alert
about it for a few minutes, and then closes. This still needs work.
This commit is contained in:
Joey Hess 2013-11-23 00:54:08 -04:00
parent 56e980215f
commit 6abaf19c41
15 changed files with 136 additions and 75 deletions

View file

@ -42,6 +42,7 @@ mkAlertButton autoclose label urlrenderer route = do
{ buttonLabel = label { buttonLabel = label
, buttonUrl = url , buttonUrl = url
, buttonAction = if autoclose then Just close else Nothing , buttonAction = if autoclose then Just close else Nothing
, buttonPrimary = True
} }
#endif #endif
@ -61,7 +62,7 @@ baseActivityAlert = Alert
, alertIcon = Just ActivityIcon , alertIcon = Just ActivityIcon
, alertCombiner = Nothing , alertCombiner = Nothing
, alertName = Nothing , alertName = Nothing
, alertButton = Nothing , alertButtons = []
} }
warningAlert :: String -> String -> Alert warningAlert :: String -> String -> Alert
@ -77,7 +78,7 @@ warningAlert name msg = Alert
, alertIcon = Just ErrorIcon , alertIcon = Just ErrorIcon
, alertCombiner = Just $ dataCombiner $ \_old new -> new , alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertName = Just $ WarningAlert name , alertName = Just $ WarningAlert name
, alertButton = Nothing , alertButtons = []
} }
errorAlert :: String -> AlertButton -> Alert errorAlert :: String -> AlertButton -> Alert
@ -93,7 +94,7 @@ errorAlert msg button = Alert
, alertIcon = Just ErrorIcon , alertIcon = Just ErrorIcon
, alertCombiner = Nothing , alertCombiner = Nothing
, alertName = Nothing , alertName = Nothing
, alertButton = Just button , alertButtons = [button]
} }
activityAlert :: Maybe TenseText -> [TenseChunk] -> Alert activityAlert :: Maybe TenseText -> [TenseChunk] -> Alert
@ -160,7 +161,7 @@ sanityCheckFixAlert msg = Alert
, alertIcon = Just ErrorIcon , alertIcon = Just ErrorIcon
, alertName = Just SanityCheckFixAlert , alertName = Just SanityCheckFixAlert
, alertCombiner = Just $ dataCombiner (++) , alertCombiner = Just $ dataCombiner (++)
, alertButton = Nothing , alertButtons = []
} }
where where
render alert = tenseWords $ alerthead : alertData alert ++ [alertfoot] render alert = tenseWords $ alerthead : alertData alert ++ [alertfoot]
@ -172,7 +173,7 @@ fsckingAlert button mr = baseActivityAlert
{ alertData = case mr of { alertData = case mr of
Nothing -> [ UnTensed $ T.pack $ "Consistency check in progress" ] Nothing -> [ UnTensed $ T.pack $ "Consistency check in progress" ]
Just r -> [ UnTensed $ T.pack $ "Consistency check of " ++ Remote.name r ++ " in progress"] Just r -> [ UnTensed $ T.pack $ "Consistency check of " ++ Remote.name r ++ " in progress"]
, alertButton = Just button , alertButtons = [button]
} }
showFscking :: UrlRenderer -> Maybe Remote -> IO (Either E.SomeException a) -> Assistant a showFscking :: UrlRenderer -> Maybe Remote -> IO (Either E.SomeException a) -> Assistant a
@ -204,7 +205,7 @@ notFsckedAlert mr button = Alert
] ]
, alertIcon = Just InfoIcon , alertIcon = Just InfoIcon
, alertPriority = High , alertPriority = High
, alertButton = Just button , alertButtons = [button]
, alertClosable = True , alertClosable = True
, alertClass = Message , alertClass = Message
, alertMessageRender = renderData , alertMessageRender = renderData
@ -223,7 +224,7 @@ canUpgradeAlert priority button = Alert
else "An upgrade of git-annex is available." else "An upgrade of git-annex is available."
, alertIcon = Just UpgradeIcon , alertIcon = Just UpgradeIcon
, alertPriority = priority , alertPriority = priority
, alertButton = Just button , alertButtons = [button]
, alertClosable = True , alertClosable = True
, alertClass = Message , alertClass = Message
, alertMessageRender = renderData , alertMessageRender = renderData
@ -234,13 +235,13 @@ canUpgradeAlert priority button = Alert
, alertData = [] , alertData = []
} }
upgradeReadyAlert :: AlertButton -> Alert upgradeReadyAlert :: [AlertButton] -> Alert
upgradeReadyAlert button = Alert upgradeReadyAlert buttons = Alert
{ alertHeader = Just $ fromString { alertHeader = Just $ fromString
"A new version of git-annex has been installed." "A new version of git-annex has been installed."
, alertIcon = Just UpgradeIcon , alertIcon = Just UpgradeIcon
, alertPriority = High , alertPriority = High
, alertButton = Just button , alertButtons = buttons
, alertClosable = True , alertClosable = True
, alertClass = Message , alertClass = Message
, alertMessageRender = renderData , alertMessageRender = renderData
@ -267,7 +268,7 @@ pairingAlert :: AlertButton -> Alert
pairingAlert button = baseActivityAlert pairingAlert button = baseActivityAlert
{ alertData = [ UnTensed "Pairing in progress" ] { alertData = [ UnTensed "Pairing in progress" ]
, alertPriority = High , alertPriority = High
, alertButton = Just button , alertButtons = [button]
} }
pairRequestReceivedAlert :: String -> AlertButton -> Alert pairRequestReceivedAlert :: String -> AlertButton -> Alert
@ -283,7 +284,7 @@ pairRequestReceivedAlert who button = Alert
, alertIcon = Just InfoIcon , alertIcon = Just InfoIcon
, alertName = Just $ PairAlert who , alertName = Just $ PairAlert who
, alertCombiner = Just $ dataCombiner $ \_old new -> new , alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertButton = Just button , alertButtons = [button]
} }
pairRequestAcknowledgedAlert :: String -> Maybe AlertButton -> Alert pairRequestAcknowledgedAlert :: String -> Maybe AlertButton -> Alert
@ -292,7 +293,7 @@ pairRequestAcknowledgedAlert who button = baseActivityAlert
, alertPriority = High , alertPriority = High
, alertName = Just $ PairAlert who , alertName = Just $ PairAlert who
, alertCombiner = Just $ dataCombiner $ \_old new -> new , alertCombiner = Just $ dataCombiner $ \_old new -> new
, alertButton = button , alertButtons = maybe [] (:[]) button
} }
xmppNeededAlert :: AlertButton -> Alert xmppNeededAlert :: AlertButton -> Alert
@ -300,7 +301,7 @@ xmppNeededAlert button = Alert
{ alertHeader = Just "Share with friends, and keep your devices in sync across the cloud." { alertHeader = Just "Share with friends, and keep your devices in sync across the cloud."
, alertIcon = Just TheCloud , alertIcon = Just TheCloud
, alertPriority = High , alertPriority = High
, alertButton = Just button , alertButtons = [button]
, alertClosable = True , alertClosable = True
, alertClass = Message , alertClass = Message
, alertMessageRender = renderData , alertMessageRender = renderData
@ -319,7 +320,7 @@ cloudRepoNeededAlert friendname button = Alert
] ]
, alertIcon = Just ErrorIcon , alertIcon = Just ErrorIcon
, alertPriority = High , alertPriority = High
, alertButton = Just button , alertButtons = [button]
, alertClosable = True , alertClosable = True
, alertClass = Message , alertClass = Message
, alertMessageRender = renderData , alertMessageRender = renderData
@ -337,7 +338,7 @@ remoteRemovalAlert desc button = Alert
"\" has been emptied, and can now be removed." "\" has been emptied, and can now be removed."
, alertIcon = Just InfoIcon , alertIcon = Just InfoIcon
, alertPriority = High , alertPriority = High
, alertButton = Just button , alertButtons = [button]
, alertClosable = True , alertClosable = True
, alertClass = Message , alertClass = Message
, alertMessageRender = renderData , alertMessageRender = renderData

View file

@ -87,7 +87,7 @@ makeAlertFiller success alert
{ alertClass = if c == Activity then c' else c { alertClass = if c == Activity then c' else c
, alertPriority = Filler , alertPriority = Filler
, alertClosable = True , alertClosable = True
, alertButton = Nothing , alertButtons = []
, alertIcon = Just $ if success then SuccessIcon else ErrorIcon , alertIcon = Just $ if success then SuccessIcon else ErrorIcon
} }
where where

View file

@ -82,7 +82,7 @@ startNamedThread urlrenderer (NamedThread afterstartupsanitycheck name a) = do
(RestartThreadR name) (RestartThreadR name)
runAssistant d $ void $ addAlert $ runAssistant d $ void $ addAlert $
(warningAlert (fromThreadName name) msg) (warningAlert (fromThreadName name) msg)
{ alertButton = Just button } { alertButtons = [button] }
#endif #endif
namedThreadId :: NamedThread -> Assistant (Maybe ThreadId) namedThreadId :: NamedThread -> Assistant (Maybe ThreadId)

View file

@ -12,6 +12,7 @@ module Assistant.Threads.UpgradeWatcher (
) where ) where
import Assistant.Common import Assistant.Common
import Assistant.Upgrade
import Utility.DirWatcher import Utility.DirWatcher
import Utility.DirWatcher.Types import Utility.DirWatcher.Types
import Config.Files import Config.Files
@ -23,6 +24,8 @@ import Assistant.DaemonStatus
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
import Assistant.WebApp.Types import Assistant.WebApp.Types
#endif #endif
import qualified Annex
import Types.Distribution
import Control.Concurrent.MVar import Control.Concurrent.MVar
import Data.Tuple.Utils import Data.Tuple.Utils
@ -77,14 +80,14 @@ changedFile urlrenderer mvar program file _status
-} -}
sanityCheck :: FilePath -> Assistant Bool sanityCheck :: FilePath -> Assistant Bool
sanityCheck program = do sanityCheck program = do
whileM (liftIO $ haswriter <||> missing) $ do untilM (liftIO $ nowriter <&&> present) $ do
debug [program, "is still being written; waiting"] debug [program, "is still being written; waiting"]
liftIO $ threadDelaySeconds (Seconds 60) liftIO $ threadDelaySeconds (Seconds 60)
debug [program, "has changed, and seems to be ready to run"] debug [program, "has changed, and seems to be ready to run"]
liftIO $ boolSystem program [Param "version"] liftIO $ boolSystem program [Param "version"]
where where
missing = not <$> doesFileExist program present = doesFileExist program
haswriter = not . null nowriter = null
. filter (`elem` [Lsof.OpenReadWrite, Lsof.OpenWriteOnly]) . filter (`elem` [Lsof.OpenReadWrite, Lsof.OpenWriteOnly])
. map snd3 . map snd3
<$> Lsof.query [program] <$> Lsof.query [program]
@ -95,9 +98,17 @@ handleUpgrade urlrenderer = do
-- (For example, other associated files may be being put into -- (For example, other associated files may be being put into
-- place.) -- place.)
liftIO $ threadDelaySeconds (Seconds 120) liftIO $ threadDelaySeconds (Seconds 120)
ifM (liftAnnex $ (==) AutoUpgrade . annexAutoUpgrade <$> Annex.getGitConfig)
( do
debug ["starting automatic upgrade"]
unattendedUpgrade
#ifdef WITH_WEBAPP #ifdef WITH_WEBAPP
button <- mkAlertButton True (T.pack "Finish Upgrade") urlrenderer ConfigFinishUpgradeR , do
void $ addAlert (upgradeReadyAlert button) finish <- mkAlertButton True (T.pack "Finish Upgrade") urlrenderer (ConfigFinishUpgradeR False)
noask <- mkAlertButton True (T.pack "Always Upgrade Automatically") urlrenderer (ConfigFinishUpgradeR True)
void $ addAlert $ upgradeReadyAlert
[finish, noask { buttonPrimary = False }]
#else #else
noop , noop
#endif #endif
)

View file

@ -51,7 +51,7 @@ data Alert = Alert
, alertIcon :: Maybe AlertIcon , alertIcon :: Maybe AlertIcon
, alertCombiner :: Maybe AlertCombiner , alertCombiner :: Maybe AlertCombiner
, alertName :: Maybe AlertName , alertName :: Maybe AlertName
, alertButton :: Maybe AlertButton , alertButtons :: [AlertButton]
} }
data AlertIcon = ActivityIcon | SyncIcon | SuccessIcon | ErrorIcon | InfoIcon | UpgradeIcon | TheCloud data AlertIcon = ActivityIcon | SyncIcon | SuccessIcon | ErrorIcon | InfoIcon | UpgradeIcon | TheCloud
@ -75,4 +75,5 @@ data AlertButton = AlertButton
{ buttonLabel :: Text { buttonLabel :: Text
, buttonUrl :: Text , buttonUrl :: Text
, buttonAction :: Maybe (AlertId -> IO ()) , buttonAction :: Maybe (AlertId -> IO ())
, buttonPrimary :: Bool
} }

61
Assistant/Upgrade.hs Normal file
View file

@ -0,0 +1,61 @@
{- git-annex assistant upgrading
-
- Copyright 2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Assistant.Upgrade where
import Assistant.Common
import qualified Annex
import Assistant.Threads.Watcher
import Assistant.Alert
import Assistant.DaemonStatus
import Assistant.NamedThread
import Utility.ThreadScheduler
import Git
import Config.Files
import Control.Concurrent
import System.Posix (getProcessID, signalProcess, sigTERM)
import System.Process (cwd)
{- Before the new assistant can be started, have to remove our
- gitAnnexUrlFile and our gitAnnexPidFile. Pausing the watcher is also
- a good idea, to avoid fighting when two assistants are running in the
- same repo.
-}
prepUpgrade :: Assistant ()
prepUpgrade = do
void $ addAlert upgradingAlert
liftIO . maybe noop (`throwTo` PauseWatcher) =<< namedThreadId watchThread
liftIO . nukeFile =<< liftAnnex (fromRepo gitAnnexUrlFile)
liftIO . nukeFile =<< liftAnnex (fromRepo gitAnnexPidFile)
{- Wait for browser to update before terminating this process. -}
postUpgrade :: IO ()
postUpgrade = void $ forkIO $ do
threadDelaySeconds (Seconds 120)
signalProcess sigTERM =<< getProcessID
{- Upgrade without interaction in the webapp.
-
- XXX If the webapp is open, this will make it stop working
- or close, with no more indication why than an alert.
-}
unattendedUpgrade :: Assistant ()
unattendedUpgrade = do
prepUpgrade
liftIO . startAssistant =<< liftAnnex (repoLocation <$> Annex.gitRepo)
liftIO postUpgrade
{- Returns once the assistant has daemonized, but possibly before it's
- listening for web connections. -}
startAssistant :: FilePath -> IO ()
startAssistant repo = do
program <- readProgramFile
(_, _, _, pid) <-
createProcess $
(proc program ["assistant"]) { cwd = Just repo }
void $ checkSuccessProcess pid

View file

@ -10,10 +10,10 @@
module Assistant.WebApp.Configurators.Local where module Assistant.WebApp.Configurators.Local where
import Assistant.WebApp.Common import Assistant.WebApp.Common
import Assistant.WebApp.OtherRepos
import Assistant.WebApp.Gpg import Assistant.WebApp.Gpg
import Assistant.WebApp.MakeRemote import Assistant.WebApp.MakeRemote
import Assistant.Sync import Assistant.Sync
import Assistant.Upgrade
import Init import Init
import qualified Git import qualified Git
import qualified Git.Construct import qualified Git.Construct

View file

@ -249,6 +249,7 @@ startLocalPairing stage oncancel alert muuid displaysecret secret = do
tid <- liftIO myThreadId tid <- liftIO myThreadId
let selfdestruct = AlertButton let selfdestruct = AlertButton
{ buttonLabel = "Cancel" { buttonLabel = "Cancel"
, buttonPrimary = True
, buttonUrl = urlrender DashboardR , buttonUrl = urlrender DashboardR
, buttonAction = Just $ const $ do , buttonAction = Just $ const $ do
oncancel oncancel

View file

@ -13,17 +13,12 @@ import Assistant.WebApp.Common
import qualified Annex import qualified Annex
import Types.Distribution import Types.Distribution
import Assistant.WebApp.OtherRepos import Assistant.WebApp.OtherRepos
import Assistant.Threads.Watcher import Assistant.Upgrade
import Assistant.Alert
import Assistant.DaemonStatus
import Assistant.NamedThread
import Utility.ThreadScheduler
import Utility.HumanTime import Utility.HumanTime
import Git import Git
import Config
import Data.Time.Clock import Data.Time.Clock
import Control.Concurrent
import System.Posix (getProcessID, signalProcess, sigTERM)
getConfigStartUpgradeR :: GitAnnexDistribution -> Handler Html getConfigStartUpgradeR :: GitAnnexDistribution -> Handler Html
getConfigStartUpgradeR d = page "Upgrade git-annex" (Just Configuration) $ do getConfigStartUpgradeR d = page "Upgrade git-annex" (Just Configuration) $ do
@ -35,28 +30,18 @@ getConfigStartUpgradeR d = page "Upgrade git-annex" (Just Configuration) $ do
{- Finish upgrade by starting the new assistant in the same repository this {- Finish upgrade by starting the new assistant in the same repository this
- one is running in, and redirecting to it. - one is running in, and redirecting to it.
- -
- Before the new assistant can be started, have to remove our - Note that only the browser tab that requested this page gets redirected.
- gitAnnexUrlFile and our gitAnnexPidFile. Pausing the watcher is also
- a good idea, to avoid fighting when two assistants are running in the
- same repo.
-
- Note that only the tag that requested this page gets redirected.
- If the user has multiple web browser tabs open to the webapp, - If the user has multiple web browser tabs open to the webapp,
- the others will show the upgradingAlert, and keep running until - the others will show the upgradingAlert, and keep running until
- this process is terminated. - this process is terminated.
-} -}
getConfigFinishUpgradeR :: Handler Html getConfigFinishUpgradeR :: Bool -> Handler Html
getConfigFinishUpgradeR = do getConfigFinishUpgradeR enableautoupgrade = do
liftAssistant $ void $ addAlert upgradingAlert when enableautoupgrade $ liftAnnex $
liftIO . maybe noop (`throwTo` PauseWatcher) =<< liftAssistant (namedThreadId watchThread) setConfig (annexConfig "autoupgrade")
liftIO . nukeFile =<< liftAnnex (fromRepo gitAnnexUrlFile) (fromAutoUpgrade AutoUpgrade)
liftIO . nukeFile =<< liftAnnex (fromRepo gitAnnexPidFile) liftAssistant prepUpgrade
reapself `after` startnewprocess liftIO postUpgrade `after` startnewprocess
where where
-- Wait for the redirect to be served to the browser
-- before terminating this process.
reapself = liftIO $ void $ forkIO $ do
threadDelaySeconds (Seconds 120)
signalProcess sigTERM =<< getProcessID
startnewprocess = switchToAssistant startnewprocess = switchToAssistant
=<< liftAnnex (repoLocation <$> Annex.gitRepo) =<< liftAnnex (repoLocation <$> Annex.gitRepo)

View file

@ -43,6 +43,7 @@ xmppNeeded = whenM (isNothing <$> liftAnnex getXMPPCreds) $ do
{ buttonLabel = "Configure a Jabber account" { buttonLabel = "Configure a Jabber account"
, buttonUrl = urlrender XMPPConfigR , buttonUrl = urlrender XMPPConfigR
, buttonAction = Just close , buttonAction = Just close
, buttonPrimary = True
} }
#else #else
xmppNeeded = return () xmppNeeded = return ()

View file

@ -17,9 +17,9 @@ import qualified Git.Config
import Config.Files import Config.Files
import qualified Utility.Url as Url import qualified Utility.Url as Url
import Utility.Yesod import Utility.Yesod
import Assistant.Upgrade
import Control.Concurrent import Control.Concurrent
import System.Process (cwd)
getRepositorySwitcherR :: Handler Html getRepositorySwitcherR :: Handler Html
getRepositorySwitcherR = page "Switch repository" Nothing $ do getRepositorySwitcherR = page "Switch repository" Nothing $ do
@ -63,13 +63,3 @@ switchToAssistant repo = do
delayed a = do delayed a = do
threadDelay 100000 -- 1/10th of a second threadDelay 100000 -- 1/10th of a second
a a
{- Returns once the assistant has daemonized, but possibly before it's
- listening for web connections. -}
startAssistant :: FilePath -> IO ()
startAssistant repo = do
program <- readProgramFile
(_, _, _, pid) <-
createProcess $
(proc program ["assistant"]) { cwd = Just repo }
void $ checkSuccessProcess pid

View file

@ -50,6 +50,7 @@ sideBarDisplay = do
let message = renderAlertMessage alert let message = renderAlertMessage alert
let messagelines = T.lines message let messagelines = T.lines message
let multiline = length messagelines > 1 let multiline = length messagelines > 1
let buttons = zip (alertButtons alert) [1..]
$(widgetFile "sidebar/alert") $(widgetFile "sidebar/alert")
{- Called by client to get a sidebar display. {- Called by client to get a sidebar display.
@ -79,16 +80,20 @@ getCloseAlert :: AlertId -> Handler ()
getCloseAlert = liftAssistant . removeAlert getCloseAlert = liftAssistant . removeAlert
{- When an alert with a button is clicked on, the button takes us here. -} {- When an alert with a button is clicked on, the button takes us here. -}
getClickAlert :: AlertId -> Handler () getClickAlert :: AlertId -> Int -> Handler ()
getClickAlert i = do getClickAlert i bnum = do
m <- alertMap <$> liftAssistant getDaemonStatus m <- alertMap <$> liftAssistant getDaemonStatus
case M.lookup i m of case M.lookup i m of
Just (Alert { alertButton = Just b }) -> do Just (Alert { alertButtons = bs })
{- Spawn a thread to run the action while redirecting. -} | length bs >= bnum -> do
let b = bs !! (bnum - 1)
{- Spawn a thread to run the action
- while redirecting. -}
case buttonAction b of case buttonAction b of
Nothing -> noop Nothing -> noop
Just a -> liftIO $ void $ forkIO $ a i Just a -> liftIO $ void $ forkIO $ a i
redirect $ buttonUrl b redirect $ buttonUrl b
| otherwise -> redirectBack
_ -> redirectBack _ -> redirectBack
htmlIcon :: AlertIcon -> Widget htmlIcon :: AlertIcon -> Widget

View file

@ -164,6 +164,10 @@ data RemovableDrive = RemovableDrive
data RepoKey = RepoKey KeyId | NoRepoKey data RepoKey = RepoKey KeyId | NoRepoKey
deriving (Read, Show, Eq, Ord) deriving (Read, Show, Eq, Ord)
instance PathPiece Bool where
toPathPiece = pack . show
fromPathPiece = readish . unpack
instance PathPiece RemovableDrive where instance PathPiece RemovableDrive where
toPathPiece = pack . show toPathPiece = pack . show
fromPathPiece = readish . unpack fromPathPiece = readish . unpack

View file

@ -22,7 +22,7 @@
/config/fsck ConfigFsckR GET POST /config/fsck ConfigFsckR GET POST
/config/fsck/preferences ConfigFsckPreferencesR POST /config/fsck/preferences ConfigFsckPreferencesR POST
/config/upgrade/start/#GitAnnexDistribution ConfigStartUpgradeR GET /config/upgrade/start/#GitAnnexDistribution ConfigStartUpgradeR GET
/config/upgrade/finish ConfigFinishUpgradeR GET /config/upgrade/finish/#Bool ConfigFinishUpgradeR GET
/config/addrepository AddRepositoryR GET /config/addrepository AddRepositoryR GET
/config/repository/new NewRepositoryR GET POST /config/repository/new NewRepositoryR GET POST
@ -103,7 +103,7 @@
/notifier/repolist/#RepoSelector NotifierRepoListR GET /notifier/repolist/#RepoSelector NotifierRepoListR GET
/alert/close/#AlertId CloseAlert GET /alert/close/#AlertId CloseAlert GET
/alert/click/#AlertId ClickAlert GET /alert/click/#AlertId/#Int ClickAlert GET
/filebrowser FileBrowserR GET POST /filebrowser FileBrowserR GET POST
/transfer/pause/#Transfer PauseTransferR GET POST /transfer/pause/#Transfer PauseTransferR GET POST

View file

@ -19,7 +19,8 @@
#{l}<br> #{l}<br>
$else $else
#{message} #{message}
$maybe button <- alertButton alert $if not (null buttons)
<br> <br>
<a .btn .btn-primary href="@{ClickAlert aid}"> $forall (button, bnum) <- buttons
<a .btn :buttonPrimary button:.btn-primary :not (buttonPrimary button):.btn-success href="@{ClickAlert aid bnum}">
#{buttonLabel button} #{buttonLabel button}