{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}

module Brick.Widgets.Calendar.Internal.Core
  ( -- * Types
    CalendarConfig(..)
  , DayLabelStyle(..)
  , OutsideMonthDisplay(..)
  , DateFormat(..)
  , CalendarState(..)
  , defaultCalendarConfig

    -- * Lenses
  , weekStart
  , dayLabelStyle
  , showDayLabels
  , outsideMonthDisplay
  , dateFormat

    -- * Resource name
  , CalendarResource(..)
  ) where

import Data.Time (DayOfWeek(..), Day)
import Lens.Micro.TH ( makeLenses )

-- | Style for displaying day labels.
data DayLabelStyle = 
    SingleChar      -- ^ Use single characters: S M T W T F S
  | DoubleChar      -- ^ Use two characters: Su Mo Tu We Th Fr Sa
  | DistinctInitials       -- ^ Use single chars with Th for Thursday: S M T W Th F S
  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)

-- | How to display days outside the current month.
data OutsideMonthDisplay =
    Hide            -- ^ Don't show days outside current month
  | ShowDimmed      -- ^ Show days outside month with dimmed styling
  | ShowNormal      -- ^ Show days outside month with normal styling
  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)

-- | Format options for displaying dates in the calendar.
data DateFormat =
    DefaultFormat   -- ^ Use default format (%b %Y for month header, digits for days)
  | CustomFormat    
    { DateFormat -> String
headerFormat :: String  -- ^ Format string for month/year header (e.g., "%B %Y")
    , DateFormat -> String
dayFormat :: String     -- ^ Format string for days (e.g., "%d")
    } -- ^ Use custom format strings from Data.Time.Format (%a, %d, etc.)
  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)

-- | Configuration for the calendar widget.
data CalendarConfig = CalendarConfig
  { CalendarConfig -> DayOfWeek
_weekStart :: DayOfWeek                -- ^ Day of week to start the calendar
  , CalendarConfig -> DayLabelStyle
_dayLabelStyle :: DayLabelStyle        -- ^ Style for day labels
  , CalendarConfig -> Bool
_showDayLabels :: Bool                 -- ^ Whether to show day labels at all
  , CalendarConfig -> OutsideMonthDisplay
_outsideMonthDisplay :: OutsideMonthDisplay -- ^ How to display days outside current month
  , CalendarConfig -> DateFormat
_dateFormat :: DateFormat              -- ^ Format to use for dates
  } 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)

-- | Default calendar configuration.
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
  }

-- | Resource name for calendar widget elements.
data CalendarResource =
    CalendarDay Int Int Int   -- ^ Resource for a day (year, month, day)
  | CalendarMonth Int Int     -- ^ Resource for month header (year, month)
  | CalendarPrev              -- ^ Resource for previous month button
  | CalendarNext              -- ^ Resource for next month button
  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)

-- | The state of the calendar widget. Make this part of your application state.
data CalendarState n = CalendarState
  { forall n. CalendarState n -> Integer
calYear :: Integer                     -- ^ Current year
  , forall n. CalendarState n -> Int
calMonth :: Int                        -- ^ Current month (1-12)
  , forall n. CalendarState n -> Maybe Day
calSelectedDay :: Maybe Day            -- ^ Currently selected day, if any
  , forall n. CalendarState n -> CalendarConfig
calConfig :: CalendarConfig            -- ^ Calendar configuration
  , forall n. CalendarState n -> CalendarResource -> n
calendarName :: CalendarResource -> n  -- ^ Constructor for wrapping calendar resources in the application's resource name type
  }

makeLenses ''CalendarConfig