{-# LANGUAGE MultiParamTypeClasses #-}

module Affection.MouseInteractable where

import Affection.Types

import qualified SDL

-- class MouseHoverable a us where
--   onHover :: a -> Affection us ()

-- | Define a mouse clickable object
class MouseClickable a us where
  onClick
    :: a               -- The object
    -> SDL.MouseButton -- The clicked button
    -> (Int, Int)      -- The coordinates of the click
    -> SDL.InputMotion -- The 'SDL.InputMotion' of the click
    -> Int             -- The number of clicks
    -> Affection us ()

-- | A helper function that checks wether provided clickables have been clicked.
-- This function does not consume provided events, but passes them on.
handleMouseClicks
  :: (Foldable t, MouseClickable clickable us)
  => SDL.EventPayload              -- ^ Piped event in
  -> t clickable                   -- ^ 'MouseClickable' elemt to be checked
  -> Affection us SDL.EventPayload -- ^ Unaltered event
handleMouseClicks e clickables =
  case e of
    SDL.MouseButtonEvent dat -> do
      mapM_ (\clickable -> do
        let SDL.P (SDL.V2 x y) = SDL.mouseButtonEventPos dat
        onClick
          clickable
          (SDL.mouseButtonEventButton dat)
          (fromIntegral x, fromIntegral y)
          (SDL.mouseButtonEventMotion dat)
          (fromIntegral $ SDL.mouseButtonEventClicks dat)
        ) clickables
      return e
    _ -> return e