{-# LANGUAGE RecordWildCards #-}

import Affection
import qualified SDL
import qualified GEGL as G
import qualified BABL as B
import qualified Data.Map.Strict as M
import Data.List as L
import Data.Maybe (fromJust)
import Control.Monad (when)
import qualified Control.Monad.Parallel as MP

import Foreign.C.Types

import Debug.Trace

main :: IO ()
main = do
  conf <- return AffectionConfig
    { initComponents = All
    , windowTitle    = "Affection: example00"
    , windowConfig   = SDL.defaultWindow
    , canvasSize     = Just (3289, 600)
    , preLoop        = return ()
    , eventLoop      = handle
    , updateLoop     = update
    , drawLoop       = draw
    , loadState      = load
    , cleanUp        = clean
    }
  withAffection conf

data UserData = UserData
  { nodeGraph    :: M.Map String G.GeglNode
  , actors       :: M.Map String (Actor String)
  , foreground   :: G.GeglBuffer
  , updateActors :: [Actor String]
  , keysDown     :: [SDL.Keycode]
  , cameraX      :: Double
  }

load :: IO UserData
load = do
  traceM "loading"
  root <- G.gegl_node_new
  traceM "new root node"
  let bgProps = props $ prop "path" ("examples/example04/panorama.jpg" :: String)
  bg <- G.gegl_node_new_child root $ G.Operation "gegl:jpg-load" bgProps
  bgScaleProps <- return $  props $ do
    prop "y" (600 :: Double)
    prop "sampler" (fromEnum G.GeglSamplerCubic)
  bgScale <- G.gegl_node_new_child root $
    G.Operation "gegl:scale-size-keepaspect" bgScaleProps
  bgTransProps <- return $ props $ do
    prop "x" (0 :: Double)
    prop "y" (0 :: Double)
    prop "sampler" (fromEnum G.GeglSamplerCubic)
  bgTrans <- G.gegl_node_new_child root $ G.Operation "gegl:translate" bgTransProps
  traceM "background"
  over <- G.gegl_node_new_child root G.defaultOverOperation
  traceM "over"
  buffer <- G.gegl_buffer_new (Just $ G.GeglRectangle 0 0 3289 600) =<<
    B.babl_format (B.PixelFormat B.RGBA B.CFfloat)
  sink <- G.gegl_node_new_child root $ G.Operation "gegl:copy-buffer" $
    props $
    prop "buffer" buffer
  traceM "buffer-sink"
  rectProps <- return $ props $ do
    prop "x" (50 :: Double)
    prop "y" (290 :: Double)
    prop "width" (20::Double)
    prop "height" (20::Double)
    prop "color" $ G.RGBA 1 0 0 0.5
  rect <- G.gegl_node_new_child root $ G.Operation "gegl:rectangle" rectProps
  traceM "rect"
  crop <- G.gegl_node_new_child root $ G.Operation "gegl:crop" $
    props $ do
      prop "width" (3289 :: Double)
      prop "height" (600 :: Double)
  G.gegl_node_link_many [bg, bgTrans, bgScale, over, crop, sink]
  _ <- G.gegl_node_connect_to rect "output" over "aux"
  rectActor <- return $ Actor (map
    (\p -> ActorProperty
      (G.propertyName p)
      (G.propertyValue p)
      (Just "rect")
      )rectProps
    ) (M.singleton "rect" rect)
  bgActor <- return $ Actor (map
    (\p -> ActorProperty
      (G.propertyName p)
      (G.propertyValue p)
      (Just "bg")
      )bgProps ++
    map (\p -> ActorProperty
      (G.propertyName p)
      (G.propertyValue p)
      (Just "scale")
      ) bgScaleProps ++
    map (\p -> ActorProperty
      (G.propertyName p)
      (G.propertyValue p)
      (Just "trans")
      ) bgTransProps
    ) (M.fromList
      [ ("bg", bg)
      , ("trans", bgTrans)
      , ("scale", bgScale)
      ])
  traceM "connections made"
  myMap <- return $ M.fromList
    [ ("root"        , root)
    , ("over"        , over)
    , ("background"  , bg)
    , ("sink"        , sink)
    , ("rect"        , rect)
    , ("crop"        , crop)
    ]
  traceM "loading complete"
  actorMap <- return $ M.fromList
    [ ("rect", rectActor)
    , ("background", bgActor)
    ]
  return UserData
    { nodeGraph    = myMap
    , actors       = actorMap
    , foreground   = buffer
    , updateActors = []
    , keysDown      = []
    , cameraX      = 0
    }

drawInit :: Affection UserData ()
drawInit = do
  ad <- get
  ud <- getAffection
  process (nodeGraph ud M.! "sink")
  present (GeglRectangle (round $ cameraX ud) 0 800 600) (foreground ud) True
  render Nothing Nothing

draw :: Affection UserData ()
draw = do
  ud@UserData{..} <- getAffection
  MP.mapM_ applyProperties updateActors
  putAffection ud
    { updateActors = []
    }
  process (nodeGraph M.! "sink")
  present (GeglRectangle (round cameraX) 0 800 600) foreground True
  render
    (Just $ G.GeglRectangle (round cameraX) 0 800 600)
    Nothing

update :: Double -> Affection UserData ()
update dt = do
  traceM "updating"

  ud <- getAffection

  traceM $ show (1 / dt) ++ " FPS"
  -- traceM $ show $ keysDown ud

  mapM_ (\code -> do
    let vel = 400 -- velocity in Pixels per second
        leg = vel * dt
    (G.PropertyDouble xpos) <-
      return $ apValue $ fromJust $ L.find (\a -> "x" == apName a) $
        actorProperties $ actors ud M.! "rect"
    nmap <- return $ M.adjust
      (updateProperties $ props $ prop "x" $ xpos +
        case code of
          SDL.KeycodeLeft ->
            if xpos - leg > 0
            then (- leg)
            else 0
          SDL.KeycodeRight ->
            if xpos + leg < 3269
            then leg
            else 0
          _ -> 0
        )
      "rect"
      (actors ud)
    let {
      offset | xpos - cameraX ud > 750 && cameraX ud + leg < 2489 && code == SDL.KeycodeRight =
                 leg
             | xpos - cameraX ud < 50  && cameraX ud - leg > 0    && code == SDL.KeycodeLeft =
                 (-leg)
             | otherwise = 0
      }
    putAffection ud
      { actors = nmap
      , updateActors = (nmap M.! "rect") : updateActors ud
      , cameraX = cameraX ud + offset
      }
    ) (keysDown ud)

handle :: SDL.EventPayload -> Affection UserData ()
handle (SDL.KeyboardEvent dat) =
  when (not (SDL.keyboardEventRepeat dat)) $ do
    ud <- getAffection
    if (SDL.keyboardEventKeyMotion dat == SDL.Pressed)
    then
      putAffection ud
        { keysDown =
            SDL.keysymKeycode (SDL.keyboardEventKeysym dat) : keysDown ud
        }
    else
      putAffection ud
        { keysDown =
            delete (SDL.keysymKeycode $ SDL.keyboardEventKeysym dat) (keysDown ud)
        }

handle (SDL.WindowClosedEvent _) = do
  traceM "seeya!"
  quit

handle _ =
  return ()

clean :: UserData -> IO ()
clean _ = return ()