Rename Timestamp type to Millisecond (#107)

* Rename Timestamp type to Millisecond

* Update Changelog
This commit is contained in:
Francisco Vallarino 2022-04-02 05:19:58 +02:00 committed by GitHub
parent 1962586e44
commit 4b32da8dff
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
19 changed files with 59 additions and 55 deletions

View File

@ -4,6 +4,7 @@
- Properly handle `SetFocusOnKey` for `textArea` ([#80](https://github.com/fjvallarino/monomer/issues/80)).
- Lens tutorial sample code ([PR #95](https://github.com/fjvallarino/monomer/pull/95) and [PR #98](https://github.com/fjvallarino/monomer/pull/98)). Thanks @Clindbergh!
- ColorPicker's numericFields vertical alignment ([PR #108](https://github.com/fjvallarino/monomer/pull/108)).
### Added
@ -14,6 +15,7 @@
- The `scroll` widget now supports a `thumbMinSize` configuration option that allows setting a minimum thumb size ([PR #100](https://github.com/fjvallarino/monomer/pull/100)).
- New field `_weAppStartTs` in `WidgetEnv`, complementary to `_weTimestamp`, representing the time in milliseconds when the application started. Added utility function `currentTimeMs` that returns their sum with a polymorphic type ([PR #103](https://github.com/fjvallarino/monomer/pull/103)).
- `style...Set` family of functions ([PR #104](https://github.com/fjvallarino/monomer/pull/104)).
- Several sizeReq helpers ([PR #106](https://github.com/fjvallarino/monomer/pull/106)).
### Changed
@ -25,6 +27,7 @@
- The `keystroke` widget now supports the `Backspace` key ([PR #74](https://github.com/fjvallarino/monomer/pull/74)).
- `Timestamp` is now a newtype. Enforce use of this type instead of `Int` when appropriate ([PR #103](https://github.com/fjvallarino/monomer/pull/103)).
- `style...` family of functions now combine new attributes with the existing ones ([PR #104](https://github.com/fjvallarino/monomer/pull/104)).
- `Timestamp` was renamed to `Millisecond`. The rationale is that since both timestamps and durations are used frequently in calculations (and in the context of Monomer timestamps and durations indeed represent time in milliseconds), having separate types for Timestamp and Duration caused more harm than good ([PR #107](https://github.com/fjvallarino/monomer/pull/107)).
### Renamed

View File

@ -92,7 +92,7 @@ The are three types of identifiers for a widget. One, as we've seen, is the
of identifying widgets. Besides nodeKey, there are two identifiers which are
mostly internal, unless you are writing custom widgets or making WidgetRequests:
- Path: This is a sequence of numbers starting from the root node, adding one
- `Path`: This is a sequence of numbers starting from the root node, adding one
number per level, until reaching the node of interest. Each number is an index
in the list of children of the parent node. The main advantages of a path are
that they clearly denote a hierarchy and that they allow to easily get the
@ -100,11 +100,11 @@ mostly internal, unless you are writing custom widgets or making WidgetRequests:
The disadvantage is that it can become invalid if widgets change positions.
Paths are used for several status related operations (focus, hover, etc), but
they should not be stored since they can become stale.
- WidgetId: The WidgetId of an item is made out of the Path and Timestamp when
the widget was initialized. This makes it unique, and allows keeping track of
the widget's path if its location in the widget tree changes. The disadvantage
is that it's not possible to deduce the WidgetId of a widget, requiring a call
to a helper function to find it.
- `WidgetId`: The WidgetId of an item is made out of the Path and the timestamp
in milliseconds when the widget was initialized. This makes it unique, and
allows keeping track of the widget's path if its location in the widget tree
changes. The disadvantage is that it's not possible to deduce the WidgetId of
a widget, requiring a call to a helper function to find it.
There are a couple of functions you can use to get the WidgetId of a node:

View File

@ -31,7 +31,7 @@ data TodoStatus
deriving (Eq, Show, Enum)
data Todo = Todo {
_todoId :: Timestamp,
_todoId :: Millisecond,
_todoType :: TodoType,
_status :: TodoStatus,
_description :: Text

View File

@ -22,7 +22,7 @@ import qualified Data.Text as T
import qualified Monomer.Lens as L
data ListItem = ListItem {
_ts :: Timestamp,
_ts :: Millisecond,
_text :: Text
} deriving (Eq, Show)

View File

@ -38,13 +38,14 @@ import Monomer.Event.Types
import Monomer.Graphics.Types
{-|
Timestamp in milliseconds. Useful for representing the time of events, ellapsed
time since start/start time of the application and length of intervals.
Time expressed in milliseconds. Useful for representing the time of events,
length of intervals, start time of the application and ellapsed time since its
start.
It can be converted from/to other numeric types using the standard functions.
-}
newtype Timestamp = Timestamp {
unTimestamp :: Word64
newtype Millisecond = Millisecond {
unMilliseconds :: Word64
} deriving (Show, Eq, Ord, Num, Enum, Bounded, Real, Integral, TextShow)
-- | Type constraints for a valid model
@ -104,7 +105,7 @@ Several WidgetRequests rely on this to find the destination of asynchronous
requests (tasks, clipboard, etc).
-}
data WidgetId = WidgetId {
_widTs :: Timestamp, -- ^ The timestamp when the instance was created.
_widTs :: Millisecond, -- ^ The timestamp when the instance was created.
_widPath :: Path -- ^ The path at creation time.
} deriving (Eq, Show, Ord, Generic)
@ -202,7 +203,7 @@ data WidgetRequest s e
| RenderOnce
-- | Useful if a widget requires periodic rendering. An optional maximum
-- number of frames can be provided.
| RenderEvery WidgetId Timestamp (Maybe Int)
| RenderEvery WidgetId Millisecond (Maybe Int)
-- | Stops a previous periodic rendering request.
| RenderStop WidgetId
{-|
@ -304,7 +305,7 @@ data WidgetEnv s e = WidgetEnv {
-- | Device pixel rate.
_weDpr :: Double,
-- | The timestamp in milliseconds when the application started.
_weAppStartTs :: Timestamp,
_weAppStartTs :: Millisecond,
-- | Provides helper funtions for calculating text size.
_weFontManager :: FontManager,
-- | Returns the node info, and its parents', given a path from root.
@ -341,7 +342,7 @@ data WidgetEnv s e = WidgetEnv {
The timestamp in milliseconds when this event/message cycle started. This
value starts from zero each time the application is run.
-}
_weTimestamp :: Timestamp,
_weTimestamp :: Millisecond,
{-|
Whether the theme changed in this cycle. Should be considered when a widget
avoids merging as optimization, as the styles may have changed.

View File

@ -75,11 +75,11 @@ data MainLoopArgs sp e ep = MainLoopArgs {
_mlOS :: Text,
_mlRenderer :: Maybe Renderer,
_mlTheme :: Theme,
_mlAppStartTs :: Timestamp,
_mlAppStartTs :: Millisecond,
_mlMaxFps :: Int,
_mlLatestRenderTs :: Timestamp,
_mlFrameStartTs :: Timestamp,
_mlFrameAccumTs :: Timestamp,
_mlLatestRenderTs :: Millisecond,
_mlFrameStartTs :: Millisecond,
_mlFrameAccumTs :: Millisecond,
_mlFrameCount :: Int,
_mlExitEvents :: [e],
_mlWidgetRoot :: WidgetNode sp ep,
@ -472,7 +472,7 @@ watchWindowResize channel = do
atomically $ writeTChan channel (MsgResize newSize)
_ -> return ()
checkRenderCurrent :: (MonomerM s e m) => Timestamp -> Timestamp -> m Bool
checkRenderCurrent :: (MonomerM s e m) => Millisecond -> Millisecond -> m Bool
checkRenderCurrent currTs renderTs = do
renderCurrent <- use L.renderRequested
schedule <- use L.renderSchedule
@ -482,14 +482,14 @@ checkRenderCurrent currTs renderTs = do
requiresRender = renderScheduleReq currTs renderTs
renderNext schedule = any requiresRender schedule
renderScheduleReq :: Timestamp -> Timestamp -> RenderSchedule -> Bool
renderScheduleReq :: Millisecond -> Millisecond -> RenderSchedule -> Bool
renderScheduleReq currTs renderTs schedule = required where
RenderSchedule _ start ms _ = schedule
stepCount = floor (fromIntegral (currTs - start) / fromIntegral ms)
stepTs = start + ms * stepCount
required = renderTs < stepTs
renderScheduleActive :: Timestamp -> RenderSchedule -> Bool
renderScheduleActive :: Millisecond -> RenderSchedule -> Bool
renderScheduleActive currTs schedule = scheduleActive where
RenderSchedule _ start ms count = schedule
stepCount = floor (fromIntegral (currTs - start) / fromIntegral ms)
@ -507,12 +507,12 @@ isMouseEntered :: [SDL.EventPayload] -> Bool
isMouseEntered eventsPayload = not status where
status = null [ e | e@SDL.WindowGainedMouseFocusEvent {} <- eventsPayload ]
getCurrentTimestamp :: MonadIO m => m Timestamp
getCurrentTimestamp :: MonadIO m => m Millisecond
getCurrentTimestamp = toMs <$> liftIO getCurrentTime
where
toMs = floor . (1e3 *) . nominalDiffTimeToSeconds . utcTimeToPOSIXSeconds
getEllapsedTimestampSince :: MonadIO m => Timestamp -> m Timestamp
getEllapsedTimestampSince :: MonadIO m => Millisecond -> m Millisecond
getEllapsedTimestampSince start = do
ts <- getCurrentTimestamp
return (ts - start)

View File

@ -517,7 +517,7 @@ handleRenderOnce previousStep = do
handleRenderEvery
:: MonomerM s e m
=> WidgetId
-> Timestamp
-> Millisecond
-> Maybe Int
-> HandlerStep s e
-> m (HandlerStep s e)

View File

@ -59,8 +59,8 @@ be provided.
-}
data RenderSchedule = RenderSchedule {
_rsWidgetId :: WidgetId,
_rsStart :: Timestamp,
_rsMs :: Timestamp,
_rsStart :: Millisecond,
_rsMs :: Millisecond,
_rsRepeat :: Maybe Int
} deriving (Eq, Show, Generic)

View File

@ -54,7 +54,7 @@ Configuration options for fade:
-}
data FadeCfg e = FadeCfg {
_fdcAutoStart :: Maybe Bool,
_fdcDuration :: Maybe Timestamp,
_fdcDuration :: Maybe Millisecond,
_fdcOnFinished :: [e]
} deriving (Eq, Show)
@ -80,7 +80,7 @@ instance CmbAutoStart (FadeCfg e) where
_fdcAutoStart = Just start
}
instance CmbDuration (FadeCfg e) Timestamp where
instance CmbDuration (FadeCfg e) Millisecond where
duration dur = def {
_fdcDuration = Just dur
}
@ -92,7 +92,7 @@ instance CmbOnFinished (FadeCfg e) e where
data FadeState = FadeState {
_fdsRunning :: Bool,
_fdsStartTs :: Timestamp
_fdsStartTs :: Millisecond
} deriving (Eq, Show, Generic)
instance Default FadeState where

View File

@ -66,7 +66,7 @@ Configuration options for slide:
data SlideCfg e = SlideCfg {
_slcDirection :: Maybe SlideDirection,
_slcAutoStart :: Maybe Bool,
_slcDuration :: Maybe Timestamp,
_slcDuration :: Maybe Millisecond,
_slcOnFinished :: [e]
} deriving (Eq, Show)
@ -94,7 +94,7 @@ instance CmbAutoStart (SlideCfg e) where
_slcAutoStart = Just start
}
instance CmbDuration (SlideCfg e) Timestamp where
instance CmbDuration (SlideCfg e) Millisecond where
duration dur = def {
_slcDuration = Just dur
}
@ -122,7 +122,7 @@ slideBottom = def { _slcDirection = Just SlideDown }
data SlideState = SlideState {
_slsRunning :: Bool,
_slsStartTs :: Timestamp
_slsStartTs :: Millisecond
} deriving (Eq, Show, Generic)
instance Default SlideState where

View File

@ -51,7 +51,7 @@ Configuration options for tooltip:
- 'tooltipFollow': if, after tooltip is displayed, it should follow the mouse.
-}
data TooltipCfg = TooltipCfg {
_ttcDelay :: Maybe Timestamp,
_ttcDelay :: Maybe Millisecond,
_ttcFollowCursor :: Maybe Bool,
_ttcMaxWidth :: Maybe Double,
_ttcMaxHeight :: Maybe Double
@ -87,7 +87,7 @@ instance CmbMaxHeight TooltipCfg where
}
-- | Delay before the tooltip is displayed when child widget is hovered.
tooltipDelay :: Timestamp -> TooltipCfg
tooltipDelay :: Millisecond -> TooltipCfg
tooltipDelay ms = def {
_ttcDelay = Just ms
}
@ -100,7 +100,7 @@ tooltipFollow = def {
data TooltipState = TooltipState {
_ttsLastPos :: Point,
_ttsLastPosTs :: Timestamp
_ttsLastPosTs :: Millisecond
} deriving (Eq, Show, Generic)
-- | Creates a tooltip for the child widget.

View File

@ -97,7 +97,7 @@ data InputFieldCfg s e a = InputFieldCfg {
-- | Caret width.
_ifcCaretWidth :: Maybe Double,
-- | Caret blink period.
_ifcCaretMs :: Maybe Timestamp,
_ifcCaretMs :: Maybe Millisecond,
-- | Character to display as text replacement. Useful for passwords.
_ifcDisplayChar :: Maybe Char,
-- | Whether input causes ResizeWidgets requests. Defaults to False.
@ -186,7 +186,7 @@ data InputFieldState a = InputFieldState {
-- | Current index into history.
_ifsHistIdx :: Int,
-- | The timestamp when focus was received (used for caret blink)
_ifsFocusStart :: Timestamp
_ifsFocusStart :: Millisecond
} deriving (Eq, Show, Typeable, Generic)
initialState :: a -> InputFieldState a
@ -209,7 +209,7 @@ initialState value = InputFieldState {
defCaretW :: Double
defCaretW = 2
defCaretMs :: Timestamp
defCaretMs :: Millisecond
defCaretMs = 500
-- | Creates an instance of an input field, with customizations in config.

View File

@ -153,7 +153,7 @@ Configuration options for dateField:
-}
data DateFieldCfg s e a = DateFieldCfg {
_dfcCaretWidth :: Maybe Double,
_dfcCaretMs :: Maybe Timestamp,
_dfcCaretMs :: Maybe Millisecond,
_dfcValid :: Maybe (WidgetData s Bool),
_dfcValidV :: [Bool -> e],
_dfcDateDelim :: Maybe Char,
@ -218,7 +218,7 @@ instance CmbCaretWidth (DateFieldCfg s e a) Double where
_dfcCaretWidth = Just w
}
instance CmbCaretMs (DateFieldCfg s e a) Timestamp where
instance CmbCaretMs (DateFieldCfg s e a) Millisecond where
caretMs ms = def {
_dfcCaretMs = Just ms
}

View File

@ -142,7 +142,7 @@ data LabelState = LabelState {
_lstTextStyle :: Maybe TextStyle,
_lstTextRect :: Rect,
_lstTextLines :: Seq TextLine,
_lstPrevResize :: (Timestamp, Bool)
_lstPrevResize :: (Millisecond, Bool)
} deriving (Eq, Show, Generic)
-- | Creates a label using the provided 'Text'.

View File

@ -124,7 +124,7 @@ Configuration options for numericField:
-}
data NumericFieldCfg s e a = NumericFieldCfg {
_nfcCaretWidth :: Maybe Double,
_nfcCaretMs :: Maybe Timestamp,
_nfcCaretMs :: Maybe Millisecond,
_nfcValid :: Maybe (WidgetData s Bool),
_nfcValidV :: [Bool -> e],
_nfcDecimals :: Maybe Int,
@ -186,7 +186,7 @@ instance CmbCaretWidth (NumericFieldCfg s e a) Double where
_nfcCaretWidth = Just w
}
instance CmbCaretMs (NumericFieldCfg s e a) Timestamp where
instance CmbCaretMs (NumericFieldCfg s e a) Millisecond where
caretMs ms = def {
_nfcCaretMs = Just ms
}

View File

@ -50,7 +50,7 @@ import qualified Monomer.Lens as L
defCaretW :: Double
defCaretW = 2
defCaretMs :: Timestamp
defCaretMs :: Millisecond
defCaretMs = 500
{-|
@ -71,7 +71,7 @@ Configuration options for textArea:
-}
data TextAreaCfg s e = TextAreaCfg {
_tacCaretWidth :: Maybe Double,
_tacCaretMs :: Maybe Timestamp,
_tacCaretMs :: Maybe Millisecond,
_tacMaxLength :: Maybe Int,
_tacMaxLines :: Maybe Int,
_tacAcceptTab :: Maybe Bool,
@ -118,7 +118,7 @@ instance CmbCaretWidth (TextAreaCfg s e) Double where
_tacCaretWidth = Just w
}
instance CmbCaretMs (TextAreaCfg s e) Timestamp where
instance CmbCaretMs (TextAreaCfg s e) Millisecond where
caretMs ms = def {
_tacCaretMs = Just ms
}
@ -193,7 +193,7 @@ data TextAreaState = TextAreaState {
_tasTextLines :: Seq TextLine,
_tasHistory :: Seq HistoryStep,
_tasHistoryIdx :: Int,
_tasFocusStart :: Timestamp
_tasFocusStart :: Millisecond
} deriving (Eq, Show, Generic)
instance Default TextAreaState where

View File

@ -60,7 +60,7 @@ Configuration options for textField:
-}
data TextFieldCfg s e = TextFieldCfg {
_tfcCaretWidth :: Maybe Double,
_tfcCaretMs :: Maybe Timestamp,
_tfcCaretMs :: Maybe Millisecond,
_tfcDisplayChar :: Maybe Char,
_tfcPlaceholder :: Maybe Text,
_tfcValid :: Maybe (WidgetData s Bool),
@ -116,7 +116,7 @@ instance CmbCaretWidth (TextFieldCfg s e) Double where
_tfcCaretWidth = Just w
}
instance CmbCaretMs (TextFieldCfg s e) Timestamp where
instance CmbCaretMs (TextFieldCfg s e) Millisecond where
caretMs ms = def {
_tfcCaretMs = Just ms
}

View File

@ -147,7 +147,7 @@ warnings in the UI, or disable buttons if needed.
-}
data TimeFieldCfg s e a = TimeFieldCfg {
_tfcCaretWidth :: Maybe Double,
_tfcCaretMs :: Maybe Timestamp,
_tfcCaretMs :: Maybe Millisecond,
_tfcValid :: Maybe (WidgetData s Bool),
_tfcValidV :: [Bool -> e],
_tfcTimeFormat :: Maybe TimeFormat,
@ -209,7 +209,7 @@ instance CmbCaretWidth (TimeFieldCfg s e a) Double where
_tfcCaretWidth = Just w
}
instance CmbCaretMs (TimeFieldCfg s e a) Timestamp where
instance CmbCaretMs (TimeFieldCfg s e a) Millisecond where
caretMs ms = def {
_tfcCaretMs = Just ms
}

View File

@ -202,14 +202,14 @@ handleWidgetIdChange oldNode result = newResult where
| otherwise = result
-- | Sends a message to the given node with a delay of n ms.
delayedMessage :: Typeable i => WidgetNode s e -> i -> Timestamp -> WidgetRequest s e
delayedMessage :: Typeable i => WidgetNode s e -> i -> Millisecond -> WidgetRequest s e
delayedMessage node msg delay = delayedMessage_ widgetId path msg delay where
widgetId = node ^. L.info . L.widgetId
path = node ^. L.info . L.path
-- | Sends a message to the given WidgetId with a delay of n ms.
delayedMessage_
:: Typeable i => WidgetId -> Path -> i -> Timestamp -> WidgetRequest s e
:: Typeable i => WidgetId -> Path -> i -> Millisecond -> WidgetRequest s e
delayedMessage_ widgetId path msg delay = RunTask widgetId path $ do
threadDelay (fromIntegral delay * 1000)
return msg