Introduce application error
This commit is contained in:
parent
4c5ff2f319
commit
c5846599ea
65
app/Main.hs
65
app/Main.hs
@ -7,6 +7,7 @@
|
|||||||
module Main (main) where
|
module Main (main) where
|
||||||
|
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
|
import Control.Monad.Trans.Except (ExceptT (..), runExceptT)
|
||||||
import Data.Proxy (Proxy (..))
|
import Data.Proxy (Proxy (..))
|
||||||
import Data.Time (Day, toGregorian)
|
import Data.Time (Day, toGregorian)
|
||||||
import Network.HTTP.Media ((//), (/:))
|
import Network.HTTP.Media ((//), (/:))
|
||||||
@ -18,11 +19,12 @@ import Servant
|
|||||||
, Handler
|
, Handler
|
||||||
, MimeRender (..)
|
, MimeRender (..)
|
||||||
, Raw
|
, Raw
|
||||||
, Server
|
|
||||||
, ServerError (..)
|
, ServerError (..)
|
||||||
|
, ServerT
|
||||||
, Tagged (..)
|
, Tagged (..)
|
||||||
, err404
|
, err404
|
||||||
, err500
|
, err500
|
||||||
|
, hoistServer
|
||||||
, runHandler
|
, runHandler
|
||||||
, serve
|
, serve
|
||||||
, (:<|>) (..)
|
, (:<|>) (..)
|
||||||
@ -45,6 +47,7 @@ import qualified Text.Blaze.Html5 as H
|
|||||||
import qualified Text.Blaze.Html5.Attributes as A
|
import qualified Text.Blaze.Html5.Attributes as A
|
||||||
|
|
||||||
import Yore.DB (DayFile (..))
|
import Yore.DB (DayFile (..))
|
||||||
|
import Yore.Error (Error (..))
|
||||||
import Yore.Time (addYears, getCurrentDay, getSecondsUntilMidnight)
|
import Yore.Time (addYears, getCurrentDay, getSecondsUntilMidnight)
|
||||||
|
|
||||||
import qualified Yore.DB as DB
|
import qualified Yore.DB as DB
|
||||||
@ -53,7 +56,7 @@ import qualified Yore.Log as Log
|
|||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = do
|
main = do
|
||||||
db <- DB.initDB "host=localhost user=yore-test port=5433 dbname=yore-test"
|
db <- DB.initDB "host=localhost user=yore-test port=5433 dbname=yore-test"
|
||||||
Warp.runSettings settings $ serve (Proxy :: Proxy API) $ server db
|
Warp.runSettings settings $ serve (Proxy :: Proxy API) $ hoistServer (Proxy :: Proxy API) nt $ server db
|
||||||
where
|
where
|
||||||
settings =
|
settings =
|
||||||
Warp.setLogger logger $
|
Warp.setLogger logger $
|
||||||
@ -74,60 +77,60 @@ main = do
|
|||||||
(BS8.unpack $ rawPathInfo req <> rawQueryString req)
|
(BS8.unpack $ rawPathInfo req <> rawQueryString req)
|
||||||
|
|
||||||
onException mbReq ex = do
|
onException mbReq ex = do
|
||||||
Log.error $ printf "unhandled exception: %s%s" (show ex) (maybe "" ((" in " ++) . requestLine) mbReq)
|
Log.error $ printf "unhandled exception%s: %s%s" (maybe "" ((" in " ++) . requestLine) mbReq) (show ex)
|
||||||
|
|
||||||
|
nt :: ExceptT Error IO a -> Handler a
|
||||||
|
nt action = MkHandler $ do
|
||||||
|
res <- runExceptT action
|
||||||
|
case res of
|
||||||
|
Left err -> do
|
||||||
|
Log.error $ show err
|
||||||
|
pure $ Left $ toServerError err
|
||||||
|
Right x ->
|
||||||
|
pure $ Right x
|
||||||
|
|
||||||
type API =
|
type API =
|
||||||
Get '[HTML] RootModel
|
Get '[HTML] RootModel
|
||||||
:<|> "today" :> "issue" :> Capture "issue" Int :> Get '[HTML] RootModel
|
:<|> "today" :> "issue" :> Capture "issue" Int :> Get '[HTML] RootModel
|
||||||
:<|> "api" :> "today" :> "issue" :> Capture "issue" Int :> "fz.pdf" :> Raw
|
:<|> "api" :> "today" :> "issue" :> Capture "issue" Int :> "fz.pdf" :> Raw
|
||||||
|
|
||||||
succeed :: (ToServerError e) => IO (Either e a) -> Handler a
|
toServerError :: Error -> ServerError
|
||||||
succeed action = MkHandler $ mapLeft toServerError <$> action
|
|
||||||
where
|
|
||||||
mapLeft f = either (Left . f) Right
|
|
||||||
|
|
||||||
class ToServerError e where
|
|
||||||
toServerError :: e -> ServerError
|
|
||||||
|
|
||||||
instance ToServerError DB.Error where
|
|
||||||
toServerError = \case
|
toServerError = \case
|
||||||
DB.ConnectionError msg ->
|
ConnectionError msg ->
|
||||||
err500 {errBody = encodeUtf8LBS $ "database connection failed:\n" ++ show msg}
|
err500 {errBody = encodeUtf8LBS $ "database connection failed:\n" ++ show msg}
|
||||||
DB.Error (Opium.ErrorNotExactlyOneRow 0) ->
|
DBError (Opium.ErrorNotExactlyOneRow 0) ->
|
||||||
err404 {errBody = "could not find record"}
|
err404 {errBody = "db error: could not find record"}
|
||||||
e ->
|
DBError msg ->
|
||||||
err500 {errBody = encodeUtf8LBS $ show e}
|
err500 {errBody = encodeUtf8LBS $ "db error: " ++ show msg}
|
||||||
|
GenericError msg ->
|
||||||
instance ToServerError String where
|
err500 {errBody = encodeUtf8LBS $ "generic error:\n" ++ show msg}
|
||||||
toServerError s =
|
|
||||||
err500 {errBody = encodeUtf8LBS s}
|
|
||||||
|
|
||||||
encodeUtf8LBS :: String -> LBS.ByteString
|
encodeUtf8LBS :: String -> LBS.ByteString
|
||||||
encodeUtf8LBS = LBS.fromStrict . Encoding.encodeUtf8 . Text.pack
|
encodeUtf8LBS = LBS.fromStrict . Encoding.encodeUtf8 . Text.pack
|
||||||
|
|
||||||
handlerToRaw :: Handler Response -> Tagged t Application
|
handlerToRaw :: ExceptT Error IO Response -> Tagged t Application
|
||||||
handlerToRaw handler = Tagged $ \_ respond -> do
|
handlerToRaw handler = Tagged $ \_ respond -> do
|
||||||
r <- runHandler handler
|
r <- runHandler $ nt handler
|
||||||
case r of
|
case r of
|
||||||
Left e ->
|
Left e ->
|
||||||
respond $ responseLBS (mkStatus e.errHTTPCode $ BS8.pack e.errReasonPhrase) e.errHeaders e.errBody
|
respond $ responseLBS (mkStatus e.errHTTPCode $ BS8.pack e.errReasonPhrase) e.errHeaders e.errBody
|
||||||
Right response ->
|
Right response ->
|
||||||
respond response
|
respond response
|
||||||
|
|
||||||
server :: DB.DB -> Server API
|
server :: DB.DB -> ServerT API (ExceptT Error IO)
|
||||||
server db = rootR :<|> todayR :<|> apiTodayR
|
server db = rootR :<|> todayR :<|> apiTodayR
|
||||||
where
|
where
|
||||||
rootR = todayR 0
|
rootR = todayR 0
|
||||||
|
|
||||||
todayR issue = do
|
todayR issue = do
|
||||||
dateThen <- succeed get100YearsAgo
|
dateThen <- ExceptT get100YearsAgo
|
||||||
count <- succeed $ DB.withConn db $ DB.getNumberOfIssues dateThen
|
count <- ExceptT $ DB.withConn db $ DB.getNumberOfIssues dateThen
|
||||||
dayFile <- succeed $ DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
dayFile <- ExceptT $ DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
||||||
pure $ RootModel dateThen dayFile issue count
|
pure $ RootModel dateThen dayFile issue count
|
||||||
|
|
||||||
apiTodayR issue = handlerToRaw $ do
|
apiTodayR issue = handlerToRaw $ do
|
||||||
dateThen <- succeed get100YearsAgo
|
dateThen <- ExceptT get100YearsAgo
|
||||||
dayFile <- succeed $ DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
dayFile <- ExceptT $ DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
||||||
let fullPath = "download" </> dayFile.relative_path
|
let fullPath = "download" </> dayFile.relative_path
|
||||||
secondsUntilMidnight <- liftIO getSecondsUntilMidnight
|
secondsUntilMidnight <- liftIO getSecondsUntilMidnight
|
||||||
pure $
|
pure $
|
||||||
@ -178,6 +181,6 @@ data HTML
|
|||||||
instance Accept HTML where
|
instance Accept HTML where
|
||||||
contentType _ = "text" // "html" /: ("charset", "utf-8")
|
contentType _ = "text" // "html" /: ("charset", "utf-8")
|
||||||
|
|
||||||
get100YearsAgo :: IO (Either String Day)
|
get100YearsAgo :: IO (Either Error Day)
|
||||||
get100YearsAgo =
|
get100YearsAgo =
|
||||||
maybe (Left "can't go back 100 years") Right . addYears (-100) <$> getCurrentDay
|
either (Left . GenericError . ("can't go back 100 years: " <>)) Right . addYears (-100) <$> getCurrentDay
|
||||||
|
|||||||
8
flake.lock
generated
8
flake.lock
generated
@ -64,11 +64,11 @@
|
|||||||
]
|
]
|
||||||
},
|
},
|
||||||
"locked": {
|
"locked": {
|
||||||
"lastModified": 1755721341,
|
"lastModified": 1756064767,
|
||||||
"narHash": "sha256-/3sjTUQG48VaMu3XC82tq1TbHTgx/xsgYHD4szQXyGM=",
|
"narHash": "sha256-SaJK9VYc/oF5aBSMSW+We8TggER4+uTAHvc2ztnLpYo=",
|
||||||
"ref": "main",
|
"ref": "main",
|
||||||
"rev": "1c32e4244eb64d31bbd49f6db8f609862225bfda",
|
"rev": "af16429d827816cf9bec69026e13f50acc3d2691",
|
||||||
"revCount": 63,
|
"revCount": 65,
|
||||||
"type": "git",
|
"type": "git",
|
||||||
"url": "https://git.pbrinkmeier.de/paul/opium"
|
"url": "https://git.pbrinkmeier.de/paul/opium"
|
||||||
},
|
},
|
||||||
|
|||||||
@ -28,12 +28,9 @@ import GHC.Generics (Generic)
|
|||||||
|
|
||||||
import qualified Database.PostgreSQL.Opium as Opium
|
import qualified Database.PostgreSQL.Opium as Opium
|
||||||
|
|
||||||
newtype DB = DB (Pool (Either Opium.ConnectionError Opium.Connection))
|
import Yore.Error (Error (..))
|
||||||
|
|
||||||
data Error
|
newtype DB = DB (Pool (Either Opium.ConnectionError Opium.Connection))
|
||||||
= ConnectionError Opium.ConnectionError
|
|
||||||
| Error Opium.Error
|
|
||||||
deriving (Show)
|
|
||||||
|
|
||||||
initDB :: Text -> IO DB
|
initDB :: Text -> IO DB
|
||||||
initDB connString = do
|
initDB connString = do
|
||||||
@ -54,7 +51,7 @@ withConn (DB connPool) f =
|
|||||||
Left connectionError ->
|
Left connectionError ->
|
||||||
pure $ Left $ ConnectionError connectionError
|
pure $ Left $ ConnectionError connectionError
|
||||||
Right conn ->
|
Right conn ->
|
||||||
either (Left . Error) Right <$> f conn
|
either (Left . DBError) Right <$> f conn
|
||||||
|
|
||||||
data DayIndex = DayIndex
|
data DayIndex = DayIndex
|
||||||
{ day_index_id :: Int
|
{ day_index_id :: Int
|
||||||
|
|||||||
11
src/Yore/Error.hs
Normal file
11
src/Yore/Error.hs
Normal file
@ -0,0 +1,11 @@
|
|||||||
|
module Yore.Error (Error (..)) where
|
||||||
|
|
||||||
|
import Data.Text (Text)
|
||||||
|
|
||||||
|
import qualified Database.PostgreSQL.Opium as Opium
|
||||||
|
|
||||||
|
data Error
|
||||||
|
= ConnectionError Opium.ConnectionError
|
||||||
|
| DBError Opium.Error
|
||||||
|
| GenericError Text
|
||||||
|
deriving (Show)
|
||||||
@ -34,9 +34,9 @@ getToday = do
|
|||||||
print now
|
print now
|
||||||
let currentDay = localDay $ zonedTimeToLocalTime now
|
let currentDay = localDay $ zonedTimeToLocalTime now
|
||||||
case addYears (-100) currentDay of
|
case addYears (-100) currentDay of
|
||||||
Just then_ ->
|
Right then_ ->
|
||||||
getIssuesByDay then_
|
getIssuesByDay then_
|
||||||
Nothing ->
|
Left _ ->
|
||||||
pure []
|
pure []
|
||||||
|
|
||||||
indexDay :: Day -> IO ()
|
indexDay :: Day -> IO ()
|
||||||
|
|||||||
@ -1,5 +1,6 @@
|
|||||||
module Yore.Time (addYears, getCurrentDay, getSecondsUntilMidnight) where
|
module Yore.Time (addYears, getCurrentDay, getSecondsUntilMidnight) where
|
||||||
|
|
||||||
|
import Data.Text (Text)
|
||||||
import Data.Time
|
import Data.Time
|
||||||
( Day
|
( Day
|
||||||
, addGregorianYearsClip
|
, addGregorianYearsClip
|
||||||
@ -11,13 +12,16 @@ import Data.Time
|
|||||||
, toGregorian
|
, toGregorian
|
||||||
, zonedTimeToLocalTime
|
, zonedTimeToLocalTime
|
||||||
)
|
)
|
||||||
|
import Text.Printf (printf)
|
||||||
|
|
||||||
addYears :: Integer -> Day -> Maybe Day
|
import qualified Data.Text as Text
|
||||||
|
|
||||||
|
addYears :: Integer -> Day -> Either Text Day
|
||||||
addYears yearOffset date
|
addYears yearOffset date
|
||||||
| isFebruary29th && not (isLeapYear year') =
|
| isFebruary29th && not (isLeapYear year') =
|
||||||
Nothing
|
Left $ Text.pack $ printf "year %d is not a leap year"
|
||||||
| otherwise =
|
| otherwise =
|
||||||
Just $ addGregorianYearsClip yearOffset date
|
Right $ addGregorianYearsClip yearOffset date
|
||||||
where
|
where
|
||||||
(year, month, day) = toGregorian date
|
(year, month, day) = toGregorian date
|
||||||
year' = year + yearOffset
|
year' = year + yearOffset
|
||||||
|
|||||||
@ -35,6 +35,7 @@ library
|
|||||||
exposed-modules:
|
exposed-modules:
|
||||||
Yore.DB
|
Yore.DB
|
||||||
, Yore.Download
|
, Yore.Download
|
||||||
|
, Yore.Error
|
||||||
, Yore.Index
|
, Yore.Index
|
||||||
, Yore.Log
|
, Yore.Log
|
||||||
, Yore.Repl
|
, Yore.Repl
|
||||||
@ -80,5 +81,6 @@ executable yore
|
|||||||
, servant-server
|
, servant-server
|
||||||
, text
|
, text
|
||||||
, time
|
, time
|
||||||
|
, transformers
|
||||||
, wai
|
, wai
|
||||||
, warp
|
, warp
|
||||||
|
|||||||
Loading…
x
Reference in New Issue
Block a user