{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveFunctor #-}
module Affection.Types
  ( Affection
  , AffectionConfig(..)
  , AffectionData(..)
  , AffectionStateInner
  , AffectionState(..)
  , InitComponents(..)
  , Angle
  -- | SDL reexports
  , SDL.WindowConfig(..)
  , SDL.WindowMode(..)
  , SDL.EventPayload(..)
  , SDL.InitFlag(..)
  , SDL.Window
  , SDL.GLContext
  ) where

import qualified SDL.Init as SDL
import qualified SDL.Video as SDL
import qualified SDL.Event as SDL
import qualified Data.Text as T

import Control.Monad.IO.Class
import Control.Monad.State.Strict
import qualified Control.Monad.Parallel as MP

import System.Clock (TimeSpec)

-- | Configuration for the aplication. needed at startup.
data AffectionConfig us = AffectionConfig
  { initComponents :: InitComponents
      -- ^ SDL components to initialize at startup
  , windowTitle    :: T.Text
      -- ^ Window title
  , windowConfig   :: SDL.WindowConfig
      -- ^ Window configuration
  , canvasSize     :: Maybe (Int, Int)
      -- ^ size of the texture canvas
  , initScreenMode :: SDL.WindowMode
      -- ^ Window mode to start in
  , loadState      :: IO us
      -- ^ Provide your own load function to create this data.
  , preLoop        :: Affection us ()
      -- ^ Actions to be performed, before loop starts
  , eventLoop      :: [SDL.EventPayload] -> Affection us ()
      -- ^ Main update function. Takes fractions of a second as input.
  , updateLoop     :: Double -> Affection us ()
      -- ^ Main update function. Takes fractions of a second as input.
  , drawLoop       :: Affection us ()
      -- ^ Function for updating graphics.
  , cleanUp        :: us -> IO ()
      -- ^ Provide your own finisher function to clean your data.
  }

-- | Components to initialize in SDL.
data InitComponents
  = All
  | Only [SDL.InitFlag]

-- | Main type for defining the look, feel and action of the whole application.
data AffectionData us = AffectionData
  { quitEvent       :: Bool               -- ^ Loop breaker.
  , userState       :: us                 -- ^ State data provided by user
  , drawWindow      :: SDL.Window         -- ^ SDL window
  , glContext       :: SDL.GLContext      -- ^ OpenGL rendering context
  , screenMode      :: SDL.WindowMode     -- ^ current screen mode
  , drawDimensions  :: (Int, Int)         -- ^ Dimensions of target surface
  , elapsedTime     :: Double             -- ^ Elapsed time in seconds
  , deltaTime       :: Double             -- ^ Elapsed time in seconds since last tick
  , sysTime         :: TimeSpec           -- ^ System time (NOT the time on the clock)
  , pausedTime      :: Bool               -- ^ Should the update loop be executed?
  }

-- | Inner 'StateT' monad for the update state
type AffectionStateInner us a = StateT us a

-- | Affection's state monad
newtype AffectionState us m a = AffectionState
  { runState :: AffectionStateInner us m a }
  deriving (Functor, Applicative, Monad, MonadIO, MonadState us)

instance MP.MonadParallel m => MP.MonadParallel (AffectionState us m)

type Affection us a = AffectionState (AffectionData us) IO a

type Angle = Double