{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module System.Taffybar.Widget.SimpleClock
  ( textClockNew
  , textClockNewWith
  , defaultClockConfig
  , ClockConfig(..)
  ) where
import           Control.Monad.IO.Class
import           Data.Time.Calendar ( toGregorian )
import qualified Data.Time.Clock as Clock
import           Data.Time.Format
import           Data.Time.LocalTime
import qualified Data.Time.Locale.Compat as L
import           Graphics.UI.Gtk
import           System.Taffybar.Widget.Generic.PollingLabel
import           System.Taffybar.Widget.Util
makeCalendar :: IO TimeZone -> IO Window
makeCalendar tzfn = do
  container <- windowNew
  cal <- calendarNew
  containerAdd container cal
  
  _ <- on container showSignal $ resetCalendarDate cal tzfn
  
  _ <- on container deleteEvent $ do
    liftIO (widgetHide container)
    return True
  return container
resetCalendarDate :: Calendar -> IO TimeZone -> IO ()
resetCalendarDate cal tzfn = do
  tz <- tzfn
  current <- Clock.getCurrentTime
  let (y,m,d) = toGregorian $ localDay $ utcToLocalTime tz current
  calendarSelectMonth cal (fromIntegral m - 1) (fromIntegral y)
  calendarSelectDay cal (fromIntegral d)
toggleCalendar :: WidgetClass w => w -> Window -> IO Bool
toggleCalendar w c = do
  isVis <- get c widgetVisible
  if isVis
    then widgetHide c
    else do
      attachPopup w "Calendar" c
      displayPopup w c
  return True
textClockNew :: MonadIO m => Maybe L.TimeLocale -> String -> Double -> m Widget
textClockNew userLocale =
  textClockNewWith cfg
  where
    cfg = defaultClockConfig { clockTimeLocale = userLocale }
data ClockConfig = ClockConfig { clockTimeZone :: Maybe TimeZone
                               , clockTimeLocale :: Maybe L.TimeLocale
                               }
                               deriving (Eq, Ord, Show)
defaultClockConfig :: ClockConfig
defaultClockConfig = ClockConfig Nothing Nothing
data TimeInfo = TimeInfo { getTZ :: IO TimeZone
                         , getLocale :: IO L.TimeLocale
                         }
systemGetTZ :: IO TimeZone
systemGetTZ = setTZ >> getCurrentTimeZone
setTZ :: IO ()
#if MIN_VERSION_time(1, 4, 2)
setTZ = return ()
#else
setTZ = c_tzset
foreign import ccall unsafe "time.h tzset"
  c_tzset :: IO ()
#endif
textClockNewWith :: MonadIO m => ClockConfig -> String -> Double -> m Widget
textClockNewWith cfg fmt updateSeconds = liftIO $ do
  let ti = TimeInfo { getTZ = maybe systemGetTZ return userZone
                    , getLocale = maybe (return L.defaultTimeLocale) return userLocale
                    }
  l    <- pollingLabelNew "" updateSeconds (getCurrentTime' ti fmt)
  ebox <- eventBoxNew
  containerAdd ebox l
  eventBoxSetVisibleWindow ebox False
  cal <- makeCalendar $ getTZ ti
  _ <- on ebox buttonPressEvent $ onClick [SingleClick] (toggleCalendar l cal)
  widgetShowAll ebox
  return (toWidget ebox)
  where
    userZone = clockTimeZone cfg
    userLocale = clockTimeLocale cfg
    
    getCurrentTime' :: TimeInfo -> String -> IO String
    getCurrentTime' ti f = do
      l <- getLocale ti
      z <- getTZ ti
      t <- Clock.getCurrentTime
      return $ formatTime l f $ utcToZonedTime z t