Factor ICAFocus into modules, change schema to include fetchedAt
This commit is contained in:
parent
d5b58e8df3
commit
da52df1e8f
|
@ -1,46 +1,40 @@
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{- TODO: refactor code into multiple modules -}
|
|
||||||
module ICAFocus where
|
module ICAFocus where
|
||||||
|
|
||||||
import qualified Network.HTTP.Client as H
|
|
||||||
import qualified Network.HTTP.Client.TLS as H
|
|
||||||
import Network.HTTP.Types.Status
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.Aeson.Types
|
import Data.Aeson.Types
|
||||||
import Data.Aeson.KeyMap
|
import Data.Aeson.KeyMap
|
||||||
import Data.Text
|
import Data.Text
|
||||||
import Text.Read
|
import Text.Read
|
||||||
|
import Data.Int (Int32)
|
||||||
import Data.ByteString.Lazy
|
import Data.ByteString.Lazy
|
||||||
import Control.Monad.Except
|
|
||||||
|
import Misc
|
||||||
|
|
||||||
newtype ImageLink = ImageLink { getLink :: String }
|
newtype ImageLink = ImageLink { getLink :: String }
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
newtype ImageData = ImageData { getData :: ByteString }
|
newtype ImageData = ImageData { getData :: ByteString }
|
||||||
|
|
||||||
|
type ProductID = Int32
|
||||||
|
|
||||||
instance Show ImageData where
|
instance Show ImageData where
|
||||||
show _ = "ImageData { ... }"
|
show _ = "ImageData { ... }"
|
||||||
|
|
||||||
data ICAFocusItem a = ICAFocusItem
|
data ICAFocusItem a = ICAFocusItem
|
||||||
{ name :: Text
|
{ name :: Text
|
||||||
|
, costPerKg :: Float
|
||||||
|
, costPerUnit :: Float
|
||||||
, image :: a
|
, image :: a
|
||||||
, pricePerUnit :: Float
|
|
||||||
, pricePerKg :: Float
|
|
||||||
}
|
}
|
||||||
deriving (Show, Functor)
|
deriving (Show, Functor)
|
||||||
|
|
||||||
type ICAFocusData = ICAFocusItem ImageLink
|
type ICAFocusData = ICAFocusItem ImageLink
|
||||||
type ICAFocusProduct = ICAFocusItem ImageData
|
type ICAFocusProduct = ICAFocusItem ImageData
|
||||||
|
|
||||||
unpackEither :: MonadFail m => Either String a -> m a
|
apiEndpoint :: ProductID -> String
|
||||||
unpackEither (Left s) = fail s
|
|
||||||
unpackEither (Right a) = pure a
|
|
||||||
|
|
||||||
apiEndpoint :: Int -> String
|
|
||||||
apiEndpoint i = "https://handlaprivatkund.ica.se/stores/1004247/api/v4/products/bop?retailerProductId=" ++ show i
|
apiEndpoint i = "https://handlaprivatkund.ica.se/stores/1004247/api/v4/products/bop?retailerProductId=" ++ show i
|
||||||
|
|
||||||
(.::) :: FromJSON a => Parser Object -> Key -> Parser a
|
|
||||||
v .:: k = v >>= (.: k)
|
|
||||||
|
|
||||||
instance FromJSON ICAFocusData where
|
instance FromJSON ICAFocusData where
|
||||||
parseJSON (Object v) = do
|
parseJSON (Object v) = do
|
||||||
productMap <- v .: "entities" .:: "product"
|
productMap <- v .: "entities" .:: "product"
|
||||||
|
@ -51,26 +45,7 @@ instance FromJSON ICAFocusData where
|
||||||
|
|
||||||
ICAFocusItem
|
ICAFocusItem
|
||||||
<$> product .: "name"
|
<$> product .: "name"
|
||||||
<*> (ImageLink <$> product .: "image" .:: "src")
|
|
||||||
<*> (unpackEither . readEither =<< product .: "price" .:: "unit" .:: "current" .:: "amount")
|
|
||||||
<*> (unpackEither . readEither =<< product .: "price" .:: "current" .:: "amount")
|
<*> (unpackEither . readEither =<< product .: "price" .:: "current" .:: "amount")
|
||||||
|
<*> (unpackEither . readEither =<< product .: "price" .:: "unit" .:: "current" .:: "amount")
|
||||||
|
<*> (ImageLink <$> product .: "image" .:: "src")
|
||||||
|
|
||||||
loadProductData :: Int -> ExceptT String IO ICAFocusData
|
|
||||||
loadProductData product_id = do
|
|
||||||
req <- H.parseRequest $ apiEndpoint product_id
|
|
||||||
resp <- liftIO $ H.httpLbs req =<< H.newManager H.tlsManagerSettings
|
|
||||||
|
|
||||||
unless (H.responseStatus resp == status200) (throwError "Error status code")
|
|
||||||
|
|
||||||
liftEither . eitherDecode $ H.responseBody resp
|
|
||||||
|
|
||||||
loadProductImage :: ICAFocusData -> ExceptT String IO ICAFocusProduct
|
|
||||||
loadProductImage x = do
|
|
||||||
req <- H.parseRequest $ (getLink . image) x
|
|
||||||
resp <- liftIO $ H.httpLbs req =<< H.newManager H.tlsManagerSettings
|
|
||||||
|
|
||||||
unless (H.responseStatus resp == status200) (throwError "Error status code")
|
|
||||||
pure $ const (ImageData (H.responseBody resp)) <$> x
|
|
||||||
|
|
||||||
loadProduct :: Int -> ExceptT String IO ICAFocusProduct
|
|
||||||
loadProduct = loadProductData >=> loadProductImage
|
|
||||||
|
|
96
backend/ICAFocus/Get.hs
Normal file
96
backend/ICAFocus/Get.hs
Normal file
|
@ -0,0 +1,96 @@
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
|
module Get where
|
||||||
|
|
||||||
|
import qualified Network.HTTP.Client as H
|
||||||
|
import qualified Network.HTTP.Client.TLS as H
|
||||||
|
import Network.HTTP.Types.Status
|
||||||
|
import Control.Monad.Except
|
||||||
|
import qualified Database.PostgreSQL.Typed as PG
|
||||||
|
import Data.Aeson
|
||||||
|
import Data.Text
|
||||||
|
import Text.Read
|
||||||
|
import Data.Int (Int32)
|
||||||
|
import Data.ByteString.Lazy
|
||||||
|
import Data.Bifunctor
|
||||||
|
|
||||||
|
import ICAFocus
|
||||||
|
|
||||||
|
import DBConfig
|
||||||
|
|
||||||
|
PG.useTPGDatabase myPGDatabase
|
||||||
|
|
||||||
|
data GetError
|
||||||
|
= ICAFocusAPIError (H.Response ByteString)
|
||||||
|
| DecodeError String
|
||||||
|
| ProductNotCached
|
||||||
|
| OutdatedEntry
|
||||||
|
| UniqueKeyViolation -- ^ should never happen
|
||||||
|
|
||||||
|
instance Show GetError where
|
||||||
|
show (ICAFocusAPIError r) = "ICAFocusAPIError { responseStatus = " ++ show (H.responseStatus r) ++ " }"
|
||||||
|
show (DecodeError e) = "DecodeError: " ++ e
|
||||||
|
show ProductNotCached = "ProductNotCached"
|
||||||
|
show OutdatedEntry = "OutdatedEntry"
|
||||||
|
show UniqueKeyViolation = "UniqueKeyViolation (should not be possible (what is postgres bro doing))"
|
||||||
|
|
||||||
|
type GetM = ExceptT GetError IO
|
||||||
|
|
||||||
|
loadProductData :: ProductID -> GetM ICAFocusData
|
||||||
|
loadProductData productId = do
|
||||||
|
req <- H.parseRequest $ apiEndpoint productId
|
||||||
|
resp <- liftIO $ H.httpLbs req =<< H.newManager H.tlsManagerSettings
|
||||||
|
|
||||||
|
unless (H.responseStatus resp == status200) (throwError $ ICAFocusAPIError resp)
|
||||||
|
|
||||||
|
liftEither . first DecodeError . eitherDecode $ H.responseBody resp
|
||||||
|
|
||||||
|
-- Fetches the image of a product, returning the product with the image data
|
||||||
|
finalizeProductImage :: ICAFocusData -> GetM ICAFocusProduct
|
||||||
|
finalizeProductImage x = do
|
||||||
|
req <- H.parseRequest $ (getLink . image) x
|
||||||
|
resp <- liftIO $ H.httpLbs req =<< H.newManager H.tlsManagerSettings
|
||||||
|
|
||||||
|
unless (H.responseStatus resp == status200) (throwError $ ICAFocusAPIError resp)
|
||||||
|
pure $ const (ImageData (H.responseBody resp)) <$> x
|
||||||
|
|
||||||
|
loadProduct :: ProductID -> GetM ICAFocusProduct
|
||||||
|
loadProduct = loadProductData >=> finalizeProductImage
|
||||||
|
|
||||||
|
fetchProduct :: PG.PGConnection -> ProductID -> GetM ICAFocusProduct
|
||||||
|
fetchProduct pg productId = do
|
||||||
|
datas <- liftIO $ PG.pgQuery pg [PG.pgSQL|
|
||||||
|
SELECT name, costPerKg, costPerUnit, image, fetchedAt + '24h' < now()
|
||||||
|
FROM ingredient_data
|
||||||
|
WHERE productId = ${productId}|]
|
||||||
|
|
||||||
|
case datas of
|
||||||
|
[] -> throwError ProductNotCached
|
||||||
|
_ : _ : _ -> throwError UniqueKeyViolation
|
||||||
|
[(_, _, _, _, Just True)] -> throwError OutdatedEntry
|
||||||
|
[(name, costPerKg, costPerUnit, image, _)] ->
|
||||||
|
pure $ ICAFocusItem name costPerKg costPerUnit (ImageData image)
|
||||||
|
|
||||||
|
cacheProduct :: PG.PGConnection -> ProductID -> ICAFocusProduct -> IO ()
|
||||||
|
cacheProduct pg productId product =
|
||||||
|
void $ PG.pgExecute pg [PG.pgSQL|
|
||||||
|
INSERT INTO ingredient_data (productId, name, costPerKg, costPerUnit, image, fetchedAt)
|
||||||
|
VALUES (${productId}, ${name product}, ${costPerKg product}, ${costPerUnit product}, ${getData (image product)}, now())
|
||||||
|
ON CONFLICT (productId)
|
||||||
|
DO UPDATE SET name = excluded.name, costPerKg = excluded.costPerKg, costPerUnit = excluded.costPerUnit, image = excluded.image, fetchedAt = excluded.fetchedAt|]
|
||||||
|
|
||||||
|
getProduct :: PG.PGConnection -> ProductID -> GetM ICAFocusProduct
|
||||||
|
getProduct pg productId = do
|
||||||
|
liftIO (runExceptT (fetchProduct pg productId)) >>= \case
|
||||||
|
Right product -> pure product
|
||||||
|
Left ProductNotCached -> refresh
|
||||||
|
Left OutdatedEntry -> refresh
|
||||||
|
Left e -> throwError e
|
||||||
|
where
|
||||||
|
refresh = do
|
||||||
|
product <- loadProduct productId
|
||||||
|
liftIO $ cacheProduct pg productId product
|
||||||
|
pure product
|
12
backend/Misc.hs
Normal file
12
backend/Misc.hs
Normal file
|
@ -0,0 +1,12 @@
|
||||||
|
module Misc where
|
||||||
|
|
||||||
|
import Data.Aeson
|
||||||
|
import Data.Aeson.Types
|
||||||
|
|
||||||
|
unpackEither :: MonadFail m => Either String a -> m a
|
||||||
|
unpackEither (Left s) = fail s
|
||||||
|
unpackEither (Right a) = pure a
|
||||||
|
|
||||||
|
(.::) :: FromJSON a => Parser Object -> Key -> Parser a
|
||||||
|
v .:: k = v >>= (.: k)
|
||||||
|
|
11
schema.sql
11
schema.sql
|
@ -1,11 +1,8 @@
|
||||||
CREATE TABLE IF NOT EXISTS ingredient
|
|
||||||
( product_id INTEGER NOT NULL PRIMARY KEY -- https://handlaprivatkund.ica.se/stores/1004247/api/v4/products/bop?retailerProductId=...
|
|
||||||
);
|
|
||||||
|
|
||||||
CREATE TABLE IF NOT EXISTS ingredient_data
|
CREATE TABLE IF NOT EXISTS ingredient_data
|
||||||
( product_id INTEGER REFERENCES ingredient(product_id)
|
( productId INTEGER NOT NULL PRIMARY KEY -- https://handlaprivatkund.ica.se/stores/1004247/api/v4/products/bop?retailerProductId=...
|
||||||
, name TEXT NOT NULL
|
, name TEXT NOT NULL
|
||||||
, cost_per_kg REAL NOT NULL
|
, costPerKg REAL NOT NULL
|
||||||
, cost_per_unit REAL NOT NULL
|
, costPerUnit REAL NOT NULL
|
||||||
, image BYTEA NOT NULL
|
, image BYTEA NOT NULL
|
||||||
|
, fetchedAt TIMESTAMP NOT NULL
|
||||||
);
|
);
|
||||||
|
|
Loading…
Reference in New Issue
Block a user