{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
module Brick.Widgets.Calendar.Internal.Core
(
CalendarConfig(..)
, DayLabelStyle(..)
, OutsideMonthDisplay(..)
, DateFormat(..)
, CalendarState(..)
, defaultCalendarConfig
, weekStart
, dayLabelStyle
, showDayLabels
, outsideMonthDisplay
, dateFormat
, CalendarResource(..)
) where
import Data.Time (DayOfWeek(..), Day)
import Lens.Micro.TH ( makeLenses )
data DayLabelStyle =
SingleChar
| DoubleChar
| DistinctInitials
deriving (Int -> DayLabelStyle -> ShowS
[DayLabelStyle] -> ShowS
DayLabelStyle -> String
(Int -> DayLabelStyle -> ShowS)
-> (DayLabelStyle -> String)
-> ([DayLabelStyle] -> ShowS)
-> Show DayLabelStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DayLabelStyle -> ShowS
showsPrec :: Int -> DayLabelStyle -> ShowS
$cshow :: DayLabelStyle -> String
show :: DayLabelStyle -> String
$cshowList :: [DayLabelStyle] -> ShowS
showList :: [DayLabelStyle] -> ShowS
Show, DayLabelStyle -> DayLabelStyle -> Bool
(DayLabelStyle -> DayLabelStyle -> Bool)
-> (DayLabelStyle -> DayLabelStyle -> Bool) -> Eq DayLabelStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DayLabelStyle -> DayLabelStyle -> Bool
== :: DayLabelStyle -> DayLabelStyle -> Bool
$c/= :: DayLabelStyle -> DayLabelStyle -> Bool
/= :: DayLabelStyle -> DayLabelStyle -> Bool
Eq)
data OutsideMonthDisplay =
Hide
| ShowDimmed
| ShowNormal
deriving (Int -> OutsideMonthDisplay -> ShowS
[OutsideMonthDisplay] -> ShowS
OutsideMonthDisplay -> String
(Int -> OutsideMonthDisplay -> ShowS)
-> (OutsideMonthDisplay -> String)
-> ([OutsideMonthDisplay] -> ShowS)
-> Show OutsideMonthDisplay
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OutsideMonthDisplay -> ShowS
showsPrec :: Int -> OutsideMonthDisplay -> ShowS
$cshow :: OutsideMonthDisplay -> String
show :: OutsideMonthDisplay -> String
$cshowList :: [OutsideMonthDisplay] -> ShowS
showList :: [OutsideMonthDisplay] -> ShowS
Show, OutsideMonthDisplay -> OutsideMonthDisplay -> Bool
(OutsideMonthDisplay -> OutsideMonthDisplay -> Bool)
-> (OutsideMonthDisplay -> OutsideMonthDisplay -> Bool)
-> Eq OutsideMonthDisplay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OutsideMonthDisplay -> OutsideMonthDisplay -> Bool
== :: OutsideMonthDisplay -> OutsideMonthDisplay -> Bool
$c/= :: OutsideMonthDisplay -> OutsideMonthDisplay -> Bool
/= :: OutsideMonthDisplay -> OutsideMonthDisplay -> Bool
Eq)
data DateFormat =
DefaultFormat
| CustomFormat
{ :: String
, DateFormat -> String
dayFormat :: String
}
deriving (Int -> DateFormat -> ShowS
[DateFormat] -> ShowS
DateFormat -> String
(Int -> DateFormat -> ShowS)
-> (DateFormat -> String)
-> ([DateFormat] -> ShowS)
-> Show DateFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DateFormat -> ShowS
showsPrec :: Int -> DateFormat -> ShowS
$cshow :: DateFormat -> String
show :: DateFormat -> String
$cshowList :: [DateFormat] -> ShowS
showList :: [DateFormat] -> ShowS
Show, DateFormat -> DateFormat -> Bool
(DateFormat -> DateFormat -> Bool)
-> (DateFormat -> DateFormat -> Bool) -> Eq DateFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DateFormat -> DateFormat -> Bool
== :: DateFormat -> DateFormat -> Bool
$c/= :: DateFormat -> DateFormat -> Bool
/= :: DateFormat -> DateFormat -> Bool
Eq)
data CalendarConfig = CalendarConfig
{ CalendarConfig -> DayOfWeek
_weekStart :: DayOfWeek
, CalendarConfig -> DayLabelStyle
_dayLabelStyle :: DayLabelStyle
, CalendarConfig -> Bool
_showDayLabels :: Bool
, CalendarConfig -> OutsideMonthDisplay
_outsideMonthDisplay :: OutsideMonthDisplay
, CalendarConfig -> DateFormat
_dateFormat :: DateFormat
} deriving (Int -> CalendarConfig -> ShowS
[CalendarConfig] -> ShowS
CalendarConfig -> String
(Int -> CalendarConfig -> ShowS)
-> (CalendarConfig -> String)
-> ([CalendarConfig] -> ShowS)
-> Show CalendarConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CalendarConfig -> ShowS
showsPrec :: Int -> CalendarConfig -> ShowS
$cshow :: CalendarConfig -> String
show :: CalendarConfig -> String
$cshowList :: [CalendarConfig] -> ShowS
showList :: [CalendarConfig] -> ShowS
Show, CalendarConfig -> CalendarConfig -> Bool
(CalendarConfig -> CalendarConfig -> Bool)
-> (CalendarConfig -> CalendarConfig -> Bool) -> Eq CalendarConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CalendarConfig -> CalendarConfig -> Bool
== :: CalendarConfig -> CalendarConfig -> Bool
$c/= :: CalendarConfig -> CalendarConfig -> Bool
/= :: CalendarConfig -> CalendarConfig -> Bool
Eq)
defaultCalendarConfig :: CalendarConfig
defaultCalendarConfig :: CalendarConfig
defaultCalendarConfig = CalendarConfig
{ _weekStart :: DayOfWeek
_weekStart = DayOfWeek
Sunday
, _dayLabelStyle :: DayLabelStyle
_dayLabelStyle = DayLabelStyle
SingleChar
, _showDayLabels :: Bool
_showDayLabels = Bool
True
, _outsideMonthDisplay :: OutsideMonthDisplay
_outsideMonthDisplay = OutsideMonthDisplay
ShowDimmed
, _dateFormat :: DateFormat
_dateFormat = DateFormat
DefaultFormat
}
data CalendarResource =
CalendarDay Int Int Int
| CalendarMonth Int Int
| CalendarPrev
| CalendarNext
deriving (Int -> CalendarResource -> ShowS
[CalendarResource] -> ShowS
CalendarResource -> String
(Int -> CalendarResource -> ShowS)
-> (CalendarResource -> String)
-> ([CalendarResource] -> ShowS)
-> Show CalendarResource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CalendarResource -> ShowS
showsPrec :: Int -> CalendarResource -> ShowS
$cshow :: CalendarResource -> String
show :: CalendarResource -> String
$cshowList :: [CalendarResource] -> ShowS
showList :: [CalendarResource] -> ShowS
Show, CalendarResource -> CalendarResource -> Bool
(CalendarResource -> CalendarResource -> Bool)
-> (CalendarResource -> CalendarResource -> Bool)
-> Eq CalendarResource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CalendarResource -> CalendarResource -> Bool
== :: CalendarResource -> CalendarResource -> Bool
$c/= :: CalendarResource -> CalendarResource -> Bool
/= :: CalendarResource -> CalendarResource -> Bool
Eq, Eq CalendarResource
Eq CalendarResource =>
(CalendarResource -> CalendarResource -> Ordering)
-> (CalendarResource -> CalendarResource -> Bool)
-> (CalendarResource -> CalendarResource -> Bool)
-> (CalendarResource -> CalendarResource -> Bool)
-> (CalendarResource -> CalendarResource -> Bool)
-> (CalendarResource -> CalendarResource -> CalendarResource)
-> (CalendarResource -> CalendarResource -> CalendarResource)
-> Ord CalendarResource
CalendarResource -> CalendarResource -> Bool
CalendarResource -> CalendarResource -> Ordering
CalendarResource -> CalendarResource -> CalendarResource
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CalendarResource -> CalendarResource -> Ordering
compare :: CalendarResource -> CalendarResource -> Ordering
$c< :: CalendarResource -> CalendarResource -> Bool
< :: CalendarResource -> CalendarResource -> Bool
$c<= :: CalendarResource -> CalendarResource -> Bool
<= :: CalendarResource -> CalendarResource -> Bool
$c> :: CalendarResource -> CalendarResource -> Bool
> :: CalendarResource -> CalendarResource -> Bool
$c>= :: CalendarResource -> CalendarResource -> Bool
>= :: CalendarResource -> CalendarResource -> Bool
$cmax :: CalendarResource -> CalendarResource -> CalendarResource
max :: CalendarResource -> CalendarResource -> CalendarResource
$cmin :: CalendarResource -> CalendarResource -> CalendarResource
min :: CalendarResource -> CalendarResource -> CalendarResource
Ord)
data CalendarState = CalendarState
{ CalendarState -> Integer
calYear :: Integer
, CalendarState -> Int
calMonth :: Int
, CalendarState -> Maybe Day
calSelectedDay :: Maybe Day
, CalendarState -> CalendarConfig
calConfig :: CalendarConfig
} deriving (Int -> CalendarState -> ShowS
[CalendarState] -> ShowS
CalendarState -> String
(Int -> CalendarState -> ShowS)
-> (CalendarState -> String)
-> ([CalendarState] -> ShowS)
-> Show CalendarState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CalendarState -> ShowS
showsPrec :: Int -> CalendarState -> ShowS
$cshow :: CalendarState -> String
show :: CalendarState -> String
$cshowList :: [CalendarState] -> ShowS
showList :: [CalendarState] -> ShowS
Show, CalendarState -> CalendarState -> Bool
(CalendarState -> CalendarState -> Bool)
-> (CalendarState -> CalendarState -> Bool) -> Eq CalendarState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CalendarState -> CalendarState -> Bool
== :: CalendarState -> CalendarState -> Bool
$c/= :: CalendarState -> CalendarState -> Bool
/= :: CalendarState -> CalendarState -> Bool
Eq)
makeLenses ''CalendarConfig