Skip to content

Commit

Permalink
updating watch to have a spinner
Browse files Browse the repository at this point in the history
  • Loading branch information
travgm committed Nov 6, 2024
1 parent d838786 commit 47dd285
Show file tree
Hide file tree
Showing 3 changed files with 45 additions and 37 deletions.
12 changes: 11 additions & 1 deletion Lib/PrettyPrinter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module PrettyPrinter (
renderTimeText
, formatTime
, displaySingleLine
, spinner
) where

import Types
Expand All @@ -30,6 +31,7 @@ import Control.Lens ((^.))
import Control.Monad.IO.Class (liftIO)
import System.Console.ANSI (clearLine, setCursorColumn)
import System.IO (hFlush, stdout)
import Control.Concurrent (threadDelay)
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import qualified Data.Time.Format as Time
Expand Down Expand Up @@ -73,6 +75,14 @@ formatTime = \case
displaySingleLine :: T.Text -> IO ()
displaySingleLine s = do
clearLine
setCursorColumn 0
setCursorColumn 2
TIO.putStr s
hFlush stdout

-- | Spinner for watch mode
spinner :: IO ()
spinner =
sequence_
[ putStr ('\r' : c : "") >> hFlush stdout >> threadDelay 250000
| c <- "-\\|/"
]
69 changes: 33 additions & 36 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,22 +15,23 @@
module Main where

import Data.Machine as M (
ProcessT,
await,
construct,
mapping,
runT_,
yield,
ProcessT,
await,
construct,
mapping,
runT_,
yield,
(~>))
import System.Console.ANSI (hideCursor, showCursor)
import Control.Exception (bracket_)
import Data.Time (ZonedTime, getZonedTime)
import Control.Monad.IO.Class (liftIO)
import Control.Concurrent (threadDelay)
import System.Info (arch, os)
import Data.Function(fix)
import Options.Applicative
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import qualified PrettyPrinter as Pretty (formatTime, displaySingleLine)
import qualified PrettyPrinter as Pretty (formatTime, displaySingleLine, spinner)
import qualified DecimalTime as DT (
localTimeToDecimal,
setCurrentDate)
Expand All @@ -51,29 +52,26 @@ data Command
parser :: Parser Command
parser = versionCmd <|> runCmd
where
versionCmd =
flag'
versionCmd = flag'
Version
( long "version"
<> short 'v'
<> help "Show version information"
)

runCmd =
fmap Run $
Config
<$> switch
( long "extended"
<> short 'e'
<> help "Show extended information including date"
)
<*> flag
SingleRun
Watch
( long "watch"
<> short 'w'
<> help "Watch mode, view as a realtime decimal clock (updates every second)"
)
runCmd = fmap Run $
Config <$> switch
( long "extended"
<> short 'e'
<> help "Show extended information including date"
)
<*> flag
SingleRun
Watch
( long "watch"
<> short 'w'
<> help "Watch mode, view as a realtime decimal clock (updates every second)"
)

-- | Get platform information for version string
createPlatformText :: T.Text
Expand Down Expand Up @@ -105,14 +103,13 @@ zonedTime = construct $ do
main :: IO ()
main = execParser opts >>= run
where
opts =
info
(parser <**> helper)
( fullDesc
<> progDesc "Decimal time clock that maps your day to 1000 decimal minutes"
<> header "dclock - decimal time clock"
)

opts = info
(parser <**> helper)
( fullDesc
<> progDesc "Decimal time clock that maps your day to 1000 decimal minutes"
<> header "dclock - decimal time clock"
)

run :: Command -> IO ()
run Version = displayVersionText
run (Run config) = runWith config
Expand All @@ -133,6 +130,6 @@ main = execParser opts >>= run
~> displayTimeText

watchClock :: Bool -> IO ()
watchClock extended' =
TIO.putStrLn "Press Ctrl-C to exit\n" >>
fix (\loop -> runClock extended' >> threadDelay 1000000 >> loop)
watchClock extended' = bracket_ hideCursor
showCursor (TIO.putStrLn "Press Ctrl-C to exit\n" >>
fix (\loop -> runClock extended' >> Pretty.spinner >> loop))
1 change: 1 addition & 0 deletions dclock.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,7 @@ executable dclock
time ^>=1.14,
machines ^>= 0.7.2,
text ^>= 2.1.1,
ansi-terminal ^>=1.1.1,
optparse-applicative ^>= 0.18.1
hs-source-dirs: app
default-language: Haskell2010
Expand Down

0 comments on commit 47dd285

Please sign in to comment.