{-# LANGUAGE RecordWildCards #-}

import Affection
import qualified SDL
import qualified GEGL as G
import qualified GEGL.FFI.Buffer as G
import qualified BABL as B
import qualified Data.Map.Strict as M

import Foreign.C.Types
import Foreign.Marshal.Utils (new)
import Foreign.Ptr (castPtr)

import Debug.Trace

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

data UserData = UserData
  { nodeGraph   :: M.Map String G.GeglNode
  , foreground  :: G.GeglBuffer
  , coordinates :: Maybe (Int, Int)
  }

load :: SDL.Surface -> IO UserData
load _ = do
  traceM "loading"
  root <- G.gegl_node_new
  traceM "new root node"
  checkerboard <- G.gegl_node_new_child root $ G.checkerboardOperation
    [ G.Property "color1" $ G.PropertyColor $ G.RGBA 0.4 0.4 0.4 1
    , G.Property "color2" $ G.PropertyColor $ G.RGBA 0.6 0.6 0.6 1
    ]
  traceM "checkerboard"
  over <- G.gegl_node_new_child root G.defaultOverOperation
  traceM "over"
  buffer@(G.GeglBuffer b) <- G.gegl_buffer_new (Just $ G.GeglRectangle 0 0 800 600) =<<
    B.babl_format (B.PixelFormat B.RGBA B.CFfloat)
  bufPtr <- new b
  sink <- G.gegl_node_new_child root $ G.Operation "gegl:copy-buffer"
    [ G.Property "buffer" $ G.PropertyBuffer buffer
    ]
  traceM "buffer-sink"
  nop <- G.gegl_node_new_child root $ G.Operation "gegl:nop" []
  traceM "nop"
  crop <- G.gegl_node_new_child root $ G.Operation "gegl:crop"
    [ G.Property "width" $ G.PropertyDouble 800
    , G.Property "height" $ G.PropertyDouble 600
    ]
  G.gegl_node_link_many [checkerboard, over, crop, sink]
  G.gegl_node_connect_to nop "output" over "aux"
  traceM "connections made"
  myMap <- return $ M.fromList
    [ ("root"        , root)
    , ("over"        , over)
    , ("background"  , checkerboard)
    , ("sink"        , sink)
    , ("nop"         , nop)
    , ("crop"        , crop)
    ]
  traceM "loading complete"
  return $ UserData
    { nodeGraph = myMap
    , foreground = buffer
    , coordinates = Nothing
    }

-- drawInit :: Affection UserData ()
-- drawInit = do
--   UserData{..} <- getAffection
--   present (nodeGraph M.! "over") foreground (GeglRectangle 0 0 800 600) True

draw :: Affection UserData ()
draw = do
  traceM "drawing"
  ad <- get
  UserData{..} <- getAffection
  SDL.V2 (CInt rw) (CInt rh) <- SDL.surfaceDimensions $ drawSurface ad
  let (w, h) = (fromIntegral rw, fromIntegral rh)
  liftIO $ clearArea foreground (GeglRectangle 0 0 w h)
  maybe (return ()) (\(x, y) ->
    drawRect'
      (nodeGraph M.! "nop")
      (G.RGBA 1 0 0 0.5)
      (Fill)
      (G.GeglRectangle (x - 10) (y - 10) 20 20)
      foreground
    ) coordinates
  liftIO $ G.gegl_node_process $ nodeGraph M.! "sink"

update :: Double -> AffectionState (AffectionData UserData) IO ()
update sec = do
  traceM "updating"
  ad <- get
  ud <- getAffection
  traceM $ (show $ 1 / sec) ++ " FPS"
  ev <- liftIO $ SDL.pollEvent
  maybe (return ()) (\e ->
    case SDL.eventPayload e of
      SDL.MouseMotionEvent dat -> do
        let (SDL.P (SDL.V2 x y)) = SDL.mouseMotionEventPos dat
        putAffection $ ud
          { coordinates = Just (fromIntegral x, fromIntegral y)
          }
      SDL.WindowClosedEvent _ -> do
        traceM "seeya!"
        put $ ad
          { quitEvent = True
          }
      _ ->
        return ()
    ) ev

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