Skip to content

Commit

Permalink
adding tests for pretty printer
Browse files Browse the repository at this point in the history
  • Loading branch information
travgm committed Nov 4, 2024
1 parent 0ddb41b commit 7fa1fc8
Show file tree
Hide file tree
Showing 6 changed files with 91 additions and 10 deletions.
8 changes: 4 additions & 4 deletions Lib/DecimalTime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@
-- Where D is decimal time, H is hour, M is minute, S is second
-----------------------------------------------------------------------------
module DecimalTime (
updateCurrentDateWithZonedTime
setCurrentDate
, localTimeToDecimal
) where

Expand Down Expand Up @@ -102,6 +102,6 @@ localTimeToDecimal s = do
decimalMinutes = round . (1000 -) . (* 1000)

-- | Set the current date with the ZonedTime
{-# INLINE updateCurrentDateWithZonedTime #-}
updateCurrentDateWithZonedTime :: ZonedTime -> ClockState -> ClockState
updateCurrentDateWithZonedTime zt state = state & (currentDate ?~ zonedTimeToLocalTime zt)
{-# INLINE setCurrentDate #-}
setCurrentDate :: ZonedTime -> ClockState -> ClockState
setCurrentDate zt state = state & (currentDate ?~ zonedTimeToLocalTime zt)
1 change: 1 addition & 0 deletions Lib/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ data ClockState = ClockState
_decimalTime :: Maybe ValidDecimalTime,
_currentDate :: Maybe LocalTime
}
deriving (Eq, Show)

type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
type Lens'' s a = L.Lens s s a a
Expand Down
4 changes: 2 additions & 2 deletions app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,7 @@ import qualified Data.Text.IO as TIO
import qualified PrettyPrinter as Pretty (formatTime, displaySingleLine)
import qualified DecimalTime as DT (
localTimeToDecimal,
updateCurrentDateWithZonedTime)
setCurrentDate)
import Types (
ClockState( .. ),
Config(..),
Expand Down Expand Up @@ -90,7 +90,7 @@ runClockProcess = \case
let state = ClockState e Nothing Nothing
runT_ $
zonedTime
~> M.mapping (`DT.updateCurrentDateWithZonedTime` state)
~> M.mapping (`DT.setCurrentDate` state)
~> M.mapping DT.localTimeToDecimal
~> M.mapping Pretty.formatTime
~> displayTimeText
Expand Down
6 changes: 4 additions & 2 deletions dclock.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -54,10 +54,12 @@ test-suite dclock-test
build-depends: base
, dclock
, time ^>=1.14
, lens ^>= 5.2.1
, lens ^>= 5.2.1
, text ^>= 2.1.1
, hspec
, QuickCheck
, hspec-discover
other-modules: DecimalTimeSpec
other-modules: DecimalTimeSpec,
PrettyPrinterSpec
build-tool-depends: hspec-discover:hspec-discover
default-language: Haskell2010
4 changes: 2 additions & 2 deletions test/DecimalTimeSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,9 +75,9 @@ spec = do
Right s -> s ^. extendedFlag == extended
Left _ -> True

describe "updateCurrentDateWithZonedTime" $ do
describe "setCurrentDate" $ do
it "verifies state _currentDate is set to LocalTime" $ property $ \tod zt ->
let state = makeTestState tod
localTime = zonedTimeToLocalTime zt
updatedState = updateCurrentDateWithZonedTime zt state
updatedState = setCurrentDate zt state
in updatedState ^. currentDate == Just localTime
78 changes: 78 additions & 0 deletions test/PrettyPrinterSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,78 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
module PrettyPrinterSpec where

import Test.Hspec
import Test.QuickCheck
import qualified Data.Text as T
import Data.Time
import Types
import Control.Lens ((^.))
import Data.Maybe (isJust, Maybe(..))
import qualified PrettyPrinter as Pretty

instance Arbitrary TimeOfDay where
arbitrary =
TimeOfDay
<$> choose (0, 23)
<*> choose (0, 59)
<*> (fromInteger <$> choose (0, 59))

instance Arbitrary ClockState where
arbitrary = do
ext <- arbitrary
dtime <- arbitrary
date <- arbitrary
return $ ClockState ext dtime date

instance Arbitrary ValidDecimalTime where
arbitrary = ValidDecimalTime . DecimalTime <$> choose (0, 1000)

instance Arbitrary LocalTime where
arbitrary =
LocalTime
<$> (fromGregorian <$> choose (2020, 2025) <*> choose (1, 12) <*> choose (1, 28))
<*> arbitrary

makeClockState :: Bool -> Maybe LocalTime -> Maybe ValidDecimalTime -> ClockState
makeClockState ext date dtime =
ClockState ext dtime date

makeValidTime :: Integer -> ValidDecimalTime
makeValidTime = ValidDecimalTime . DecimalTime

spec :: Spec
spec = do
describe "renderTimeText" $ do
it "renders NEW for 0" $ do
let state = makeClockState False Nothing (Just $ makeValidTime 0)
Pretty.renderTimeText state "" `shouldBe` "Decimal time: NEW"

it "renders number for non-zero time" $ do
let state = makeClockState False Nothing (Just $ makeValidTime 500)
Pretty.renderTimeText state "" `shouldBe` "Decimal time: 500"

it "handles Nothing decimal time" $ do
let state = makeClockState False Nothing Nothing
Pretty.renderTimeText state "" `shouldBe` "Decimal time: Invalid time"

describe "formatTime" $ do
it "formats error message" $ do
Pretty.formatTime (Left "test error") `shouldBe` "Decimal time: test error"

it "formats normal time without extended info" $ do
let state = makeClockState False Nothing (Just $ makeValidTime 500)
Pretty.formatTime (Right state) `shouldBe` "Decimal time: 500"

it "formats time with date when extended" $ do
let date = LocalTime (fromGregorian 2024 1 1) midnight
state = makeClockState True (Just date) (Just $ makeValidTime 500)
Pretty.formatTime (Right state) `shouldBe` "Decimal time: 500 (2024-01-01)"

it "formats NEW with date when extended" $ do
let date = LocalTime (fromGregorian 2024 1 1) midnight
state = makeClockState True (Just date) (Just $ makeValidTime 0)
Pretty.formatTime (Right state) `shouldBe` "Decimal time: NEW (2024-01-01)"

it "always starts with 'Decimal time: '" $ property $ \state ->
T.isPrefixOf "Decimal time: " (Pretty.formatTime $ Right state)

0 comments on commit 7fa1fc8

Please sign in to comment.