yammat/Handler/Home.hs

63 lines
2.3 KiB
Haskell
Raw Normal View History

2015-08-09 21:16:33 +02:00
-- yammat - Yet Another MateMAT
-- Copyright (C) 2015 Amedeo Molnár
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published
-- by the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
2015-04-04 06:46:33 +02:00
module Handler.Home where
import Import
import qualified Text.Read as R
2015-04-16 02:51:08 +02:00
import Data.Maybe
2015-04-04 06:46:33 +02:00
-- This is a handler function for the GET request method on the HomeR
-- resource pattern. All of your resource patterns are defined in
-- config/routes
--
-- The majority of the code you will write in Yesod lives in these handler
-- functions. You can spread them across multiple files if you are so
-- inclined, or create a single monolithic file.
getHomeR :: Handler Html
getHomeR = do
beverages <- runDB $ selectList [BeverageAmount !=. 0] [Desc BeverageIdent]
time <- liftIO getCurrentTime
2015-07-22 07:08:59 +02:00
secs <- return $ (R.read $ formatTime defaultTimeLocale "%s" time) - 2592000
2015-04-04 06:46:33 +02:00
users <- runDB $ selectList [UserTimestamp >=. secs] [Asc UserIdent]
defaultLayout $ do
$(widgetFile "home")
postHomeR :: Handler Html
postHomeR = do
error "Not yet implemented"
getReactivateR :: Handler Html
getReactivateR = do
time <- liftIO getCurrentTime
2015-07-21 09:15:09 +02:00
secs <- return $ (R.read $ formatTime defaultTimeLocale "%s" time) - 2592000
users <- runDB $ selectList [UserTimestamp <. secs] [Asc UserIdent]
2015-04-04 06:46:33 +02:00
defaultLayout $ do
$(widgetFile "reactivate")
getUserReactivateR :: UserId -> Handler Html
getUserReactivateR uId = do
mUser <- runDB $ get uId
case mUser of
Just user -> do
time <- liftIO getCurrentTime
secs <- return $ R.read $ formatTime defaultTimeLocale "%s" time
runDB $ update uId [UserTimestamp =. secs]
2015-04-10 00:40:58 +02:00
setMessageI MsgUserReactivated
2015-04-04 06:46:33 +02:00
redirect $ HomeR
Nothing -> do
2015-04-10 00:40:58 +02:00
setMessageI MsgUserUnknown
2015-04-04 06:46:33 +02:00
redirect $ HomeR