Skip to content

Instantly share code, notes, and snippets.

@shapr
Created September 20, 2023 22:34
Show Gist options
  • Save shapr/71c853fdb55efc6cbabab555a77fde16 to your computer and use it in GitHub Desktop.
Save shapr/71c853fdb55efc6cbabab555a77fde16 to your computer and use it in GitHub Desktop.
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Control.Concurrent
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Data.Void
import Network.URI.Encode (encode)
import System.Exit
import System.IO
import Text.Megaparsec
import Text.Megaparsec.Char
import Text.Megaparsec.Char.Lexer (decimal)
type Parser = Parsec Void Text
{-
1. pipe text into this program
2. URI encode the text
3. print the encoded string
-}
secondsTillDone :: Int
secondsTillDone = 5
main :: IO ()
main = do
-- stuff <- getContents
hPutStr stdout "this is a prompt > "
hFlush stdout
stuff <- TIO.getLine
putStrLn ""
let timeTill :: Maybe HowLong = parseMaybe pHowLong stuff
case timeTill of
Just parsedTime -> doneYetHL $ toEnum . fromEnum $ parsedTime
Nothing -> do
TIO.putStrLn $ T.pack (show stuff) <> " is not a valid time, are you SURE you want to launch missiles?"
exitWith $ ExitFailure 1
doneYetHL :: HowLong -> IO ()
doneYetHL (S 0) = pure ()
doneYetHL (MS 0 0) = pure ()
doneYetHL (HMS 0 0 0) = pure ()
doneYetHL hms = do
threadDelay 1000000
putStr "\ESC[A"
putStrLn $ "done in " <> show hms
doneYetHL (toEnum $ (fromEnum hms) - 1)
howLongToInt :: HowLong -> Int
howLongToInt (S s) = if s <= 60 then s else error "you almost got me!"
howLongToInt (MS m s) = if m <= 60 then (m * 60 + howLongToInt (S s)) else error "not this time!"
howLongToInt (HMS h m s) = h * 3600 + howLongToInt (MS m s)
-- intToHowLong :: Int -> HowLong
wiggleTheString :: String -> String
wiggleTheString = encode
data HowLong
= S Int
| MS Int Int
| HMS
Int
Int
Int
instance Show HowLong where
show (S s) = pad s
show (MS m s) = pad m <> ":" <> show (S s)
show (HMS h m s) = pad h <> ":" <> show (MS m s)
instance Enum HowLong where
fromEnum (S s) = s
fromEnum (MS m s) = 60 * m + s
fromEnum (HMS h m s) = 3600 * h + 60 * m + s
toEnum n = HMS (n `div` 3600) ((n `div` 60) `mod` 60) (n `mod` 60)
pad :: Int -> String
pad n = if n < 10 then ("0" <> show n) else show n
pHowLong :: Parser HowLong
pHowLong = try hms <|> try ms <|> s
where
s = S <$> decimal <* eof
ms = MS <$> decimal <* string ":" <*> decimal <* eof
hms =
HMS
<$> decimal
<* string ":"
<*> decimal
<* string ":"
<*> decimal
<* eof
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment