{-# LANGUAGE OverloadedStrings #-} import RatingChgkInfo import RatingChgkInfo.Types.Unsafe (TournamentId (..), PlayerId (..)) import Data.Aeson import Data.Text (Text) import qualified Data.Text as T import qualified Data.Text.IO as T import Data.Time import System.Directory (withCurrentDirectory) import System.Environment (getArgs) main :: IO () main = do args <- getArgs case args of [rootDir, "town", townStr, town] -> withCurrentDirectory rootDir $ case readMaybe townStr of Nothing -> usage Just townId -> workTown townId (T.pack town) Nothing >>= mapM_ print [rootDir, townPagesStr] -> withCurrentDirectory rootDir $ case readMaybe townPagesStr of Nothing -> usage Just townPages -> work townPages _ -> usage usage :: IO () usage = do die "Usage: calendar-rating " work :: Int -> IO () work townPages = do ets <- fmap (fmap concat . sequence) $ forM [1..townPages] $ towns . Just case ets of Left err -> T.putStrLn $ decodeUtf8 err Right ts -> do ss <- forM ts $ \Town{ townId = ident, townName = town, townOtherName = other } -> do T.putStrLn town workTown ident town other encodeFile "names.json" $ map fst $ filter (not . null . snd) $ zip ts ss workTown :: Int -> Text -> Maybe Text -> IO [SynchTown] workTown ident town other = do now <- getCurrentTime ests <- synchTown ident case ests of Left err -> T.putStrLn (decodeUtf8 err) >> pure [] Right sts -> do let fname = "t" ++ show ident ++ ".ics" let events = filter ((==ClaimAccepted) . stStatus) sts unless (null events) $ T.writeFile fname $ T.intercalate "\r\n" [ calStart , T.intercalate "\r\n" $ map (mkEvent now town other) events , calEnd ] pure events calStart :: Text calStart = T.intercalate "\r\n" [ "BEGIN:VCALENDAR" , "VERSION:2.0" , "PRODID:-//calendar.chgk.me/EN" , "METHOD:PUBLISH" ] calEnd :: Text calEnd = "END:VCALENDAR" mkEvent :: UTCTime -> Text -> Maybe Text -> SynchTown -> Text mkEvent now town other SynchTown{ stTournamentId = TournamentId tid , stTournament = tourn , stRepresentativeId = PlayerId rid , stRepresentative = rep , stTime = time } = T.intercalate "\r\n" [ "BEGIN:VEVENT" , "UID:" `T.append` uid , "DTSTAMP:" `T.append` ts , "DTSTART;TZID=Europe/Moscow:" `T.append` start , "SUMMARY:" `T.append` summary , "ORGANIZER:" `T.append` org , "LOCATION:" `T.append` loc , "URL:" `T.append` url , "DESCRIPTION:" `T.append` desc , "END:VEVENT" ] where uid = T.concat [ "t", tid, "-r", rid, "@calendar.chgk.me" ] format :: FormatTime t => t -> Text format = T.pack . formatTime defaultTimeLocale "%Y%m%dT%H%M%S" ts = format now `T.append` "Z" start = format time summary = tourn org = rep loc = T.concat $ town : maybe [] pure other url = T.concat [ "https://rating.chgk.info/tournament/", tid ] desc = T.concat [ "Представитель: ", rep, "\\n", "Турнир: ", url]