Skip to content

Commit

Permalink
Move wijkanders fetch to it's own file
Browse files Browse the repository at this point in the history
  • Loading branch information
The1Penguin committed Oct 20, 2024
1 parent d00570e commit 9d37593
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 13 deletions.
10 changes: 1 addition & 9 deletions src/Model.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,6 @@ import Data.Thyme ( _localDay
, _utctDay
)
import Data.Thyme.Time ( toThyme )
import Data.Text.Lazy ( pack )
import Lens.Micro.Platform ( (^.)
, (&)
, (%~)
Expand All @@ -57,15 +56,12 @@ import System.Directory ( listDirectory
, getAccessTime
, removeFile )
import Text.Printf ( printf )
import Network.Wreq ( get
, responseBody )

import Config
import Model.Types
import Model.Karen
import Model.Wijkanders
import Model.Linsen
import Util ( (^.^) )

-- | Refreshes menus.
-- The refresh function evaluates to `Some monad m => m (View model, Update signal)`,
Expand Down Expand Up @@ -131,8 +127,7 @@ update = do
"21f31565-5c2b-4b47-d2a1-08d558129279"
, karenR "S.M.A.K." "smak" "3ac68e11-bcee-425e-d2a8-08d558129279"
, karenR "L's Kitchen" "ls-kitchen" "c74da2cf-aa1a-4d3a-9ba6-08d5569587a1"
, liftIO (get wijkandersAPIURL) >>= (^.^ responseBody) <&>
Restaurant "Wijkanders" (pack wijkandersAPIURL) . getWijkanders day'
, fetchAndCreateWijkanders day'
, fetchAndCreateLinsen day'
]

Expand All @@ -142,7 +137,4 @@ update = do
liftIO getCurrentTime >>=
liftIO . flip writeFile (show e) . flip (printf "%s/%s%s.txt" path) (name r) . show
_ -> pure ()

return (View rest textday d)
where
wijkandersAPIURL = "https://www.wijkanders.se/restaurangen"
26 changes: 22 additions & 4 deletions src/Model/Wijkanders.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,6 @@
{-# LANGUAGE LambdaCase, OverloadedStrings #-}
module Model.Wijkanders
( getWijkanders
, hasDate
( fetchAndCreateWijkanders
)
where

Expand All @@ -10,6 +9,8 @@ import Control.Arrow ( (***)
, (>>>)
)
import Control.Monad ( (<=<) )
import Control.Monad.Catch ( MonadThrow )
import Control.Monad.IO.Class ( MonadIO (liftIO) )
import Data.Attoparsec.ByteString.Lazy ( maybeResult
, parse
, skip
Expand All @@ -18,9 +19,11 @@ import Data.Attoparsec.ByteString.Lazy ( maybeResult
, takeWhile1
)
import Data.ByteString.Lazy ( ByteString )
import Data.Text.Lazy ( pack )
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BL8
import Data.Functor ( (<&>) )
import Data.Maybe ( mapMaybe )
import Data.Text.Encoding.Error ( ignore )
import Data.Text.Encoding ( encodeUtf8 )
Expand All @@ -36,6 +39,8 @@ import Data.Thyme ( Day
)
import qualified Data.Word8 as W8
import Lens.Micro.Platform ( view )
import Network.Wreq ( get
, responseBody )
import Safe ( atMay )
import Text.HTML.TagSoup ( (~==)
, (~/=)
Expand All @@ -47,9 +52,13 @@ import Text.HTML.TagSoup ( (~==)
import Text.HTML.TagSoup.Match ( tagText )

import Model.Types ( Menu(..)
, NoMenu(..)
, NoMenu(..), Restaurant (Restaurant)
)
import Util ( removeWhitespaceTags )
import Util ( removeWhitespaceTags
, (^.^) )

wijkandersAPIURL :: String
wijkandersAPIURL = "https://www.wijkanders.se/restaurangen"

-- | Looks for strings looking like dates, dd/mm where d and m are digits.
-- ..and gives them in another order to play nice with the
Expand Down Expand Up @@ -109,3 +118,12 @@ getWijkanders d b = go b
>>> \case
[] -> Left (NMParseError "Wijkanders failed" b)
xs -> Right xs

fetchAndCreateWijkanders
:: (MonadIO m, MonadThrow m)
=> Day
-> m Restaurant
fetchAndCreateWijkanders day =
liftIO (get wijkandersAPIURL) >>=
(^.^ responseBody) <&>
Restaurant "Wijkanders" (pack wijkandersAPIURL) . getWijkanders day

0 comments on commit 9d37593

Please sign in to comment.