Compare commits
No commits in common. "f2a136d27c479cc733fc6e207f4b2a027e0d1bcb" and "dbea1c549f6e2d2f5b7f35ad1640222f7b7928c9" have entirely different histories.
f2a136d27c
...
dbea1c549f
57
app/Main.hs
57
app/Main.hs
@ -20,19 +20,22 @@ import Data.Text (Text)
|
|||||||
import Data.Time (Day, LocalTime (..), TimeOfDay (..), ZonedTime (..), addDays, toGregorian)
|
import Data.Time (Day, LocalTime (..), TimeOfDay (..), ZonedTime (..), addDays, toGregorian)
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import Network.HTTP.Media ((//), (/:))
|
import Network.HTTP.Media ((//), (/:))
|
||||||
import Network.HTTP.Types (Status (..))
|
import Network.HTTP.Types (Status (..), mkStatus, status200)
|
||||||
import Network.Wai (Request (..))
|
import Network.Wai (Application, Request (..), Response, responseFile, responseLBS)
|
||||||
import Servant
|
import Servant
|
||||||
( Accept (..)
|
( Accept (..)
|
||||||
, Capture
|
, Capture
|
||||||
, Get
|
, Get
|
||||||
, Handler
|
, Handler
|
||||||
, MimeRender (..)
|
, MimeRender (..)
|
||||||
|
, Raw
|
||||||
, ServerError (..)
|
, ServerError (..)
|
||||||
, ServerT
|
, ServerT
|
||||||
|
, Tagged (..)
|
||||||
, err404
|
, err404
|
||||||
, err500
|
, err500
|
||||||
, hoistServer
|
, hoistServer
|
||||||
|
, runHandler
|
||||||
, serve
|
, serve
|
||||||
, (:<|>) (..)
|
, (:<|>) (..)
|
||||||
, (:>)
|
, (:>)
|
||||||
@ -59,13 +62,18 @@ import Yore.Download (downloadInto)
|
|||||||
import Yore.Error (Error (..))
|
import Yore.Error (Error (..))
|
||||||
import Yore.Schedule (schedule)
|
import Yore.Schedule (schedule)
|
||||||
import Yore.Scrape (Issue (..), getIssuesByDay)
|
import Yore.Scrape (Issue (..), getIssuesByDay)
|
||||||
import Yore.Servant (GetSendfile, Sendfile (..))
|
|
||||||
import Yore.Time (addYears, getCurrentDay, getSecondsUntilMidnight)
|
import Yore.Time (addYears, getCurrentDay, getSecondsUntilMidnight)
|
||||||
|
|
||||||
import qualified Envy
|
import qualified Envy
|
||||||
import qualified Yore.DB as DB
|
import qualified Yore.DB as DB
|
||||||
import qualified Yore.Log as Log
|
import qualified Yore.Log as Log
|
||||||
|
|
||||||
|
newtype ConnectionString = ConnectionString String
|
||||||
|
deriving (Show)
|
||||||
|
|
||||||
|
instance Envy.ReadEnvVar ConnectionString where
|
||||||
|
readEnvVar = fmap ConnectionString . Envy.readEnvVar
|
||||||
|
|
||||||
data ConfigT f = Config
|
data ConfigT f = Config
|
||||||
{ yorePort :: f =@@ Int ? 3000
|
{ yorePort :: f =@@ Int ? 3000
|
||||||
, yoreDownloadDir :: f =@@ FilePath ? "./download"
|
, yoreDownloadDir :: f =@@ FilePath ? "./download"
|
||||||
@ -106,9 +114,12 @@ doIndex :: Config -> DB -> ExceptT Error IO ()
|
|||||||
doIndex cfg db =
|
doIndex cfg db =
|
||||||
catchE
|
catchE
|
||||||
( DB.withTransaction db $ \conn -> do
|
( DB.withTransaction db $ \conn -> do
|
||||||
forM_ [0, 1, 2] $ \i -> do
|
dayThen <- getTodayWithOffset (-100) 0
|
||||||
dayThen <- getTodayWithOffset (-100) i
|
|
||||||
indexDay cfg dayThen conn
|
indexDay cfg dayThen conn
|
||||||
|
dayThen2 <- getTodayWithOffset (-100) 1
|
||||||
|
indexDay cfg dayThen2 conn
|
||||||
|
dayThen3 <- getTodayWithOffset (-100) 2
|
||||||
|
indexDay cfg dayThen3 conn
|
||||||
)
|
)
|
||||||
(Log.error . show)
|
(Log.error . show)
|
||||||
|
|
||||||
@ -133,9 +144,6 @@ runServer cfg db =
|
|||||||
(statusCode status)
|
(statusCode status)
|
||||||
(requestLine req)
|
(requestLine req)
|
||||||
|
|
||||||
onException mbReq ex = do
|
|
||||||
Log.error $ printf "unhandled exception%s: %s%s" (maybe "" ((" in " ++) . requestLine) mbReq) (show ex)
|
|
||||||
|
|
||||||
requestLine :: Request -> String
|
requestLine :: Request -> String
|
||||||
requestLine req =
|
requestLine req =
|
||||||
printf
|
printf
|
||||||
@ -143,6 +151,9 @@ runServer cfg db =
|
|||||||
(BS8.unpack $ requestMethod req)
|
(BS8.unpack $ requestMethod req)
|
||||||
(BS8.unpack $ rawPathInfo req <> rawQueryString req)
|
(BS8.unpack $ rawPathInfo req <> rawQueryString req)
|
||||||
|
|
||||||
|
onException mbReq ex = do
|
||||||
|
Log.error $ printf "unhandled exception%s: %s%s" (maybe "" ((" in " ++) . requestLine) mbReq) (show ex)
|
||||||
|
|
||||||
nt :: ExceptT Error IO a -> Handler a
|
nt :: ExceptT Error IO a -> Handler a
|
||||||
nt action = MkHandler $ do
|
nt action = MkHandler $ do
|
||||||
res <- runExceptT action
|
res <- runExceptT action
|
||||||
@ -153,6 +164,11 @@ nt action = MkHandler $ do
|
|||||||
Right x ->
|
Right x ->
|
||||||
pure $ Right x
|
pure $ Right x
|
||||||
|
|
||||||
|
type API =
|
||||||
|
Get '[HTML] RootModel
|
||||||
|
:<|> "today" :> "issue" :> Capture "issue" Int :> Get '[HTML] RootModel
|
||||||
|
:<|> "api" :> "today" :> "issue" :> Capture "issue" Int :> "fz.pdf" :> Raw
|
||||||
|
|
||||||
toServerError :: Error -> ServerError
|
toServerError :: Error -> ServerError
|
||||||
toServerError = \case
|
toServerError = \case
|
||||||
ConnectionError msg ->
|
ConnectionError msg ->
|
||||||
@ -167,10 +183,14 @@ toServerError = \case
|
|||||||
encodeUtf8LBS :: String -> LBS.ByteString
|
encodeUtf8LBS :: String -> LBS.ByteString
|
||||||
encodeUtf8LBS = LBS.fromStrict . Encoding.encodeUtf8 . Text.pack
|
encodeUtf8LBS = LBS.fromStrict . Encoding.encodeUtf8 . Text.pack
|
||||||
|
|
||||||
type API =
|
handlerToRaw :: ExceptT Error IO Response -> Tagged t Application
|
||||||
Get '[HTML] RootModel
|
handlerToRaw handler = Tagged $ \_ respond -> do
|
||||||
:<|> "today" :> "issue" :> Capture "issue" Int :> Get '[HTML] RootModel
|
r <- runHandler $ nt handler
|
||||||
:<|> "api" :> "today" :> "issue" :> Capture "issue" Int :> "fz.pdf" :> GetSendfile
|
case r of
|
||||||
|
Left e ->
|
||||||
|
respond $ responseLBS (mkStatus e.errHTTPCode $ BS8.pack e.errReasonPhrase) e.errHeaders e.errBody
|
||||||
|
Right response ->
|
||||||
|
respond response
|
||||||
|
|
||||||
server :: Config -> DB -> ServerT API (ExceptT Error IO)
|
server :: Config -> DB -> ServerT API (ExceptT Error IO)
|
||||||
server cfg db = rootR :<|> todayR :<|> apiTodayR
|
server cfg db = rootR :<|> todayR :<|> apiTodayR
|
||||||
@ -183,20 +203,19 @@ server cfg db = rootR :<|> todayR :<|> apiTodayR
|
|||||||
dayFile <- DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
dayFile <- DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
||||||
pure $ RootModel dateThen dayFile issue count
|
pure $ RootModel dateThen dayFile issue count
|
||||||
|
|
||||||
apiTodayR issue = do
|
apiTodayR issue = handlerToRaw $ do
|
||||||
dateThen <- ExceptT get100YearsAgo
|
dateThen <- ExceptT get100YearsAgo
|
||||||
dayFile <- DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
dayFile <- DB.withConn db $ DB.getDayFileByIssue dateThen issue
|
||||||
let fullPath = cfg.yoreDownloadDir </> dayFile.relative_path
|
let fullPath = cfg.yoreDownloadDir </> dayFile.relative_path
|
||||||
secondsUntilMidnight <- liftIO getSecondsUntilMidnight
|
secondsUntilMidnight <- liftIO getSecondsUntilMidnight
|
||||||
pure
|
pure $
|
||||||
Sendfile
|
responseFile
|
||||||
{ headers =
|
status200
|
||||||
[ ("content-type", "application/pdf")
|
[ ("content-type", "application/pdf")
|
||||||
, ("cache-control", BS8.pack $ printf "public, max-age=%d" secondsUntilMidnight)
|
, ("cache-control", BS8.pack $ printf "public, max-age=%d" secondsUntilMidnight)
|
||||||
]
|
]
|
||||||
, path =
|
|
||||||
fullPath
|
fullPath
|
||||||
}
|
Nothing
|
||||||
|
|
||||||
data RootModel = RootModel Day DB.DayFile Int Int
|
data RootModel = RootModel Day DB.DayFile Int Int
|
||||||
|
|
||||||
@ -261,7 +280,7 @@ indexDay cfg dayThen conn = do
|
|||||||
issues <- liftIO $ getIssuesByDay dayThen
|
issues <- liftIO $ getIssuesByDay dayThen
|
||||||
paths <- forM issues $ \issue -> do
|
paths <- forM issues $ \issue -> do
|
||||||
Log.info $ printf "downloading %s" issue.url
|
Log.info $ printf "downloading %s" issue.url
|
||||||
path <- downloadInto cfg.yoreDownloadDir issue.url
|
path <- liftIO $ downloadInto cfg.yoreDownloadDir issue.url
|
||||||
pure (issue.label, path)
|
pure (issue.label, path)
|
||||||
Log.info "creating DB entries"
|
Log.info "creating DB entries"
|
||||||
dayIndex <- DB.createDayIndex dayThen conn
|
dayIndex <- DB.createDayIndex dayThen conn
|
||||||
|
|||||||
@ -1,8 +1,3 @@
|
|||||||
\restrict VcBcXJr0fe2fRf2im7J0PCentZxDeYMChdNcReN5LtHeQrg2nXyh5MelIBAiGsO
|
|
||||||
|
|
||||||
-- Dumped from database version 17.6
|
|
||||||
-- Dumped by pg_dump version 17.6
|
|
||||||
|
|
||||||
SET statement_timeout = 0;
|
SET statement_timeout = 0;
|
||||||
SET lock_timeout = 0;
|
SET lock_timeout = 0;
|
||||||
SET idle_in_transaction_session_timeout = 0;
|
SET idle_in_transaction_session_timeout = 0;
|
||||||
@ -129,8 +124,6 @@ ALTER TABLE ONLY yore.day_file
|
|||||||
-- PostgreSQL database dump complete
|
-- PostgreSQL database dump complete
|
||||||
--
|
--
|
||||||
|
|
||||||
\unrestrict VcBcXJr0fe2fRf2im7J0PCentZxDeYMChdNcReN5LtHeQrg2nXyh5MelIBAiGsO
|
|
||||||
|
|
||||||
|
|
||||||
--
|
--
|
||||||
-- Dbmate schema migrations
|
-- Dbmate schema migrations
|
||||||
|
|||||||
6
flake.lock
generated
6
flake.lock
generated
@ -40,11 +40,11 @@
|
|||||||
},
|
},
|
||||||
"nixpkgs": {
|
"nixpkgs": {
|
||||||
"locked": {
|
"locked": {
|
||||||
"lastModified": 1758518877,
|
"lastModified": 1752536923,
|
||||||
"narHash": "sha256-1K1c6vNr/N1PfM77DqKINXQ/oCxA0W1ZJ80sfNzWu0w=",
|
"narHash": "sha256-fdgPZR7VFSSRIQKOJLcs3qCJBWM64Uak0gAGtWTYAd8=",
|
||||||
"owner": "nixos",
|
"owner": "nixos",
|
||||||
"repo": "nixpkgs",
|
"repo": "nixpkgs",
|
||||||
"rev": "033cc13ab4c1a60b3527b242755aa625001ff1f9",
|
"rev": "c665e4d918eda5d78a175ed8d300809c44932160",
|
||||||
"type": "github"
|
"type": "github"
|
||||||
},
|
},
|
||||||
"original": {
|
"original": {
|
||||||
|
|||||||
@ -2,8 +2,7 @@
|
|||||||
|
|
||||||
module Yore.Download (downloadInto) where
|
module Yore.Download (downloadInto) where
|
||||||
|
|
||||||
import Control.Exception (Exception, IOException, catch)
|
import Control.Monad (guard)
|
||||||
import Control.Monad.Trans.Except (ExceptT (..))
|
|
||||||
import Data.Maybe (fromJust)
|
import Data.Maybe (fromJust)
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Network.HTTP.Req hiding (queryParam)
|
import Network.HTTP.Req hiding (queryParam)
|
||||||
@ -15,8 +14,6 @@ import qualified Data.Text as Text
|
|||||||
import qualified Data.UUID.V4 as UUID
|
import qualified Data.UUID.V4 as UUID
|
||||||
import qualified Text.URI as URI
|
import qualified Text.URI as URI
|
||||||
|
|
||||||
import Yore.Error (Error (..))
|
|
||||||
|
|
||||||
-- | Download a URL and save it to a directory.
|
-- | Download a URL and save it to a directory.
|
||||||
-- Returns the path of the downloaded file relative to the directory.
|
-- Returns the path of the downloaded file relative to the directory.
|
||||||
downloadInto
|
downloadInto
|
||||||
@ -24,30 +21,22 @@ downloadInto
|
|||||||
-- ^ Directory where to store the file.
|
-- ^ Directory where to store the file.
|
||||||
-> Text
|
-> Text
|
||||||
-- ^ The URL to download.
|
-- ^ The URL to download.
|
||||||
-> ExceptT Error IO FilePath
|
-> IO FilePath
|
||||||
downloadInto downloadDir textUrl =
|
downloadInto downloadDir textUrl = download >>= save
|
||||||
download >>= save
|
|
||||||
where
|
where
|
||||||
download :: ExceptT Error IO LBS.ByteString
|
download :: IO LBS.ByteString
|
||||||
download = toExceptT (handle @HttpException) $ do
|
download = do
|
||||||
uri <- URI.mkURI textUrl
|
uri <- URI.mkURI textUrl
|
||||||
let (url, opts) = fromJust $ useHttpsURI uri
|
let (url, opts) = fromJust $ useHttpsURI uri
|
||||||
res <- runReq defaultHttpConfig $ req GET url NoReqBody lbsResponse opts
|
res <- runReq defaultHttpConfig $ req GET url NoReqBody lbsResponse opts
|
||||||
|
guard $ responseStatusCode res == 200
|
||||||
pure $ responseBody res
|
pure $ responseBody res
|
||||||
|
|
||||||
save :: LBS.ByteString -> ExceptT Error IO FilePath
|
save :: LBS.ByteString -> IO FilePath
|
||||||
save contents = toExceptT (handle @IOException) $ do
|
save contents = do
|
||||||
let suffix = takeExtension $ Text.unpack textUrl
|
let suffix = takeExtension $ Text.unpack textUrl
|
||||||
uuid <- UUID.nextRandom
|
uuid <- UUID.nextRandom
|
||||||
let fullPath = downloadDir </> show uuid <.> suffix
|
let fullPath = downloadDir </> show uuid <.> suffix
|
||||||
createDirectoryIfMissing True downloadDir
|
createDirectoryIfMissing True downloadDir
|
||||||
LBS.writeFile fullPath contents
|
LBS.writeFile fullPath contents
|
||||||
pure $ makeRelative downloadDir fullPath
|
pure $ makeRelative downloadDir fullPath
|
||||||
|
|
||||||
toExceptT :: (Exception e) => (e -> Error) -> IO a -> ExceptT Error IO a
|
|
||||||
toExceptT showException f =
|
|
||||||
ExceptT $ (Right <$> f) `catch` (pure . Left . showException)
|
|
||||||
|
|
||||||
handle :: (Show e) => e -> Error
|
|
||||||
handle =
|
|
||||||
GenericError . Text.pack . show
|
|
||||||
|
|||||||
@ -1,31 +0,0 @@
|
|||||||
{-# LANGUAGE OverloadedRecordDot #-}
|
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
|
||||||
|
|
||||||
module Yore.Servant (GetSendfile, Sendfile (..)) where
|
|
||||||
|
|
||||||
import Network.HTTP.Types (ResponseHeaders, status200)
|
|
||||||
import Network.Wai (responseFile)
|
|
||||||
import Servant (HasServer (..))
|
|
||||||
import Servant.Server.Internal.Delayed (runAction)
|
|
||||||
import Servant.Server.Internal.RouteResult (RouteResult (..))
|
|
||||||
import Servant.Server.Internal.Router (Router' (..))
|
|
||||||
|
|
||||||
-- | Servant route type that responds with a file using @sendfile@.
|
|
||||||
data GetSendfile
|
|
||||||
|
|
||||||
data Sendfile = Sendfile
|
|
||||||
{ headers :: ResponseHeaders
|
|
||||||
-- ^ The headers to send along with the file, e.g. @content-type@ or cache information.
|
|
||||||
, path :: FilePath
|
|
||||||
-- ^ The file to respond with.
|
|
||||||
}
|
|
||||||
deriving (Show)
|
|
||||||
|
|
||||||
instance HasServer GetSendfile context where
|
|
||||||
type ServerT GetSendfile m = m Sendfile
|
|
||||||
|
|
||||||
hoistServerWithContext _ _ nt = nt
|
|
||||||
|
|
||||||
route _ _ action = RawRouter $ \env request respond ->
|
|
||||||
runAction action env request respond $ \sendfile ->
|
|
||||||
Route $ responseFile status200 sendfile.headers sendfile.path Nothing
|
|
||||||
@ -41,7 +41,6 @@ library
|
|||||||
, Yore.Schedule
|
, Yore.Schedule
|
||||||
, Yore.Scrape
|
, Yore.Scrape
|
||||||
, Yore.Time
|
, Yore.Time
|
||||||
, Yore.Servant
|
|
||||||
hs-source-dirs:
|
hs-source-dirs:
|
||||||
src
|
src
|
||||||
build-depends:
|
build-depends:
|
||||||
@ -50,19 +49,16 @@ library
|
|||||||
, directory
|
, directory
|
||||||
, filepath
|
, filepath
|
||||||
, html-parse
|
, html-parse
|
||||||
, http-types
|
|
||||||
, lens
|
, lens
|
||||||
, modern-uri
|
, modern-uri
|
||||||
, mtl
|
, mtl
|
||||||
, opium
|
, opium
|
||||||
, req
|
, req
|
||||||
, resource-pool
|
, resource-pool
|
||||||
, servant-server
|
|
||||||
, text
|
, text
|
||||||
, time
|
, time
|
||||||
, transformers
|
, transformers
|
||||||
, uuid
|
, uuid
|
||||||
, wai
|
|
||||||
|
|
||||||
executable yore
|
executable yore
|
||||||
import: shared-options
|
import: shared-options
|
||||||
|
|||||||
Loading…
x
Reference in New Issue
Block a user