timecodeg/src/Main.hs

109 lines
3.5 KiB
Haskell
Raw Normal View History

2022-02-08 19:20:34 +00:00
module Main where
import Data.Char
import Control.Concurrent
import System.Environment
import Data.Time.Clock
import Data.Time.Format
import Data.Time.Clock.POSIX
2022-02-11 16:44:08 +00:00
import Network.HTTP.Conduit
import Network.HTTP.Simple (getResponseStatusCode, getResponseBody)
2022-02-08 19:20:34 +00:00
import Data.List.Split
import Data.Algorithm.Diff
import Data.Algorithm.DiffOutput
2022-02-10 06:57:23 +00:00
import Data.ByteString.Lazy.UTF8 (toString)
2022-02-10 07:24:54 +00:00
import System.IO
2022-02-08 19:20:34 +00:00
data GeneratorState = IsRunning | IsFinished
deriving (Eq)
2022-02-10 06:57:23 +00:00
isChanged :: Diff f -> Bool
isChanged (First _) = True
isChanged _ = False
hasDiff :: [a] -> Bool
hasDiff [] = False
hasDiff _ = True
-- Changes as one string if they exsists
2022-02-10 06:57:23 +00:00
getChanges :: [String] -> [String] -> Maybe String
getChanges now before = if (hasDiff ch) then Just res else Nothing
where ch = filter isChanged diff
diff = getDiff now before
res = foldr (\(First x) y -> x ++ " \n " ++ y) "" ch
2022-02-08 19:44:40 +00:00
2022-02-10 07:58:18 +00:00
-- TODO: Should return signal to stop the script if there's a checkbox with a keyword `stop`
2022-02-09 05:06:36 +00:00
showRunning :: [String] -> GeneratorState
2022-02-08 19:20:34 +00:00
showRunning html = IsRunning
-- Printing time diff in %H:%M:%S format
myFormatDiffTime :: (UTCTime, UTCTime) -> String
myFormatDiffTime (a,b)= formatTime defaultTimeLocale "%H:%M:%S" . posixSecondsToUTCTime $ diffUTCTime a b
appendToFile :: String -> String -> IO()
appendToFile filename str = do
file <- openFile filename AppendMode
hPutStrLn file str
hClose file
-- Printing changes is they exsists
2022-02-10 07:58:18 +00:00
genOutput :: Maybe String -> String -> String -> IO ()
genOutput (Just changes) time timecodeFile= do
appendToFile timecodeFile $ time ++ "\n " ++ changes
2022-02-10 07:58:18 +00:00
genOutput Nothing _ _ = return()
2022-02-10 06:57:23 +00:00
2022-02-10 07:24:54 +00:00
-- Returning fetched url as a string separated by \n
2022-02-11 16:44:08 +00:00
fetchFile :: String -> IO (Either String [String])
2022-02-10 07:09:44 +00:00
fetchFile url = do
2022-02-11 16:44:08 +00:00
request <- parseRequest url
manager <- newManager tlsManagerSettings
response <- httpLbs request manager
let statusCode = getResponseStatusCode response
if statusCode `div` 100 == 2 then do
return $ Right ((splitOn ("\n")) . toString $ getResponseBody response)
else do
return $ Left (show statusCode)
-- Main Loop
2022-02-10 07:58:18 +00:00
timecodeGenerator :: GeneratorState -> [String] -> UTCTime -> String -> String -> IO ()
timecodeGenerator IsFinished _ _ _ _ = return ()
timecodeGenerator IsRunning prevFile time url timecodeFile = do
2022-02-11 16:44:08 +00:00
fetched <- fetchFile url
case fetched of
Right newFile -> do
currTime <- getCurrentTime
let changes = getChanges newFile prevFile
let diffTime = myFormatDiffTime (currTime, time)
2022-02-11 16:44:08 +00:00
genOutput changes diffTime timecodeFile
-- Waiting for 1 second
threadDelay 10000
-- Creating a loop until `IsFinished`
if showRunning newFile == IsRunning then
timecodeGenerator IsRunning newFile time url timecodeFile
else
timecodeGenerator IsFinished newFile time url timecodeFile
Left err -> do
print err
timecodeGenerator IsRunning prevFile time url timecodeFile
2022-02-10 07:58:18 +00:00
-- Commandline arguments:
-- 1. Link to markdown file
-- 2. File to write timecodes to
2022-02-08 19:20:34 +00:00
main :: IO ()
main = do
2022-02-10 07:58:18 +00:00
args <- getArgs
let url:timecodeFile:xs = args
2022-02-08 19:20:34 +00:00
time <- getCurrentTime
2022-02-10 07:09:44 +00:00
file <- fetchFile url
2022-02-11 16:44:08 +00:00
case file of
Left e -> do
putStrLn $ (++) "Error: " $ show e
Right file -> do
appendToFile timecodeFile $ "New Timecodes starts here \n "
appendToFile timecodeFile $ show time
timecodeGenerator IsRunning file time url timecodeFile
2022-02-10 07:58:18 +00:00
--let url = "https://hd.socks.town/s/h0jnEJQWy/download"
--let timecodeFile = "timecodes.md"