module Graphics.UI.WX.Events
            ( 
               Event
             , on
             , mapEvent
             , propagateEvent
             
             
             , Selecting, select
             
             , Commanding, command
             
             , Reactive
             , mouse, keyboard
             , closing, idle, resize, focus, activate
             , Paint
             , paint, paintRaw, repaint
             
             
             , enter, leave, motion, drag
             , click, unclick, doubleClick
             , clickRight, unclickRight
             
             , anyKey, key, charKey
             , enterKey,tabKey,escKey,helpKey
             , delKey,homeKey,endKey
             , pgupKey,pgdownKey
             , downKey,upKey,leftKey,rightKey
             , rebind
            
            
            , Modifiers(..)
            , showModifiers
            , noneDown, justShift, justAlt, justControl, justMeta, isNoneDown
            , isNoShiftAltControlDown
            
            , EventMouse (..)
            , showMouse
            , mousePos, mouseModifiers
            
            , EventCalendar(..)
            , calendarEvent
            
            , EventKey (..), Key(..)
            , keyKey, keyModifiers, keyPos
            , showKey, showKeyModifiers
             
             , newEvent
            ) where
import Graphics.UI.WXCore hiding (Event)
import Graphics.UI.WX.Types
import Graphics.UI.WX.Attributes
import Graphics.UI.WX.Layout
import Graphics.UI.WX.Classes
data Event w a  = Event (Attr w a)
on :: Event w a -> Attr w a
on (Event attr)
  = attr
mapEvent :: (a -> b) -> (a -> b -> a) -> Event w a -> Event w b
mapEvent get set (Event attr)
  = Event (mapAttr get set attr)
class Selecting w where
  
  select :: Event w (IO ())
class Commanding w where
  
  command :: Event w (IO ())
class Reactive w where
  mouse     :: Event w (EventMouse -> IO ())
  keyboard  :: Event w (EventKey -> IO ())
  closing   :: Event w (IO ())
  idle      :: Event w (IO Bool)
  resize    :: Event w (IO ())
  focus     :: Event w (Bool -> IO ())
  activate  :: Event w (Bool -> IO ())
class Paint w where
  
  
  
  paint     :: Event w (DC () -> Rect -> IO ())
  
  
  paintRaw  :: Event w (DC () -> Rect -> [Rect] -> IO ())
  
  repaint   :: w -> IO ()
click :: Reactive w => Event w (Point -> IO ())
click
  = mouseFilter "click" filter
  where
    filter (MouseLeftDown point mod)  = isNoShiftAltControlDown mod
    filter other                      = False
unclick :: Reactive w => Event w (Point -> IO ())
unclick
  = mouseFilter "unclick" filter
  where
    filter (MouseLeftUp point mod)  = isNoShiftAltControlDown mod
    filter other                    = False
doubleClick :: Reactive w => Event w (Point -> IO ())
doubleClick
  = mouseFilter "doubleClick" filter
  where
    filter (MouseLeftDClick point mod) = isNoShiftAltControlDown mod
    filter other                       = False
drag :: Reactive w => Event w (Point -> IO ())
drag
  = mouseFilter "drag" filter
  where
    filter (MouseLeftDrag point mod)  = isNoShiftAltControlDown mod
    filter other                      = False
motion :: Reactive w => Event w (Point -> IO ())
motion
  = mouseFilter "motion" filter
  where
    filter (MouseMotion point mod)  = isNoShiftAltControlDown mod
    filter other                    = False
clickRight :: Reactive w => Event w (Point -> IO ())
clickRight
  = mouseFilter "clickRight" filter
  where
    filter (MouseRightDown point mod)  = isNoShiftAltControlDown mod
    filter other                       = False
unclickRight :: Reactive w => Event w (Point -> IO ())
unclickRight
  = mouseFilter "unclickRight" filter
  where
    filter (MouseRightUp point mod)  = isNoShiftAltControlDown mod
    filter other                     = False
enter :: Reactive w => Event w (Point -> IO ())
enter
  = mouseFilter "enter" filter
  where
    filter (MouseEnter point mod)  = True
    filter other                   = False
leave :: Reactive w => Event w (Point -> IO ())
leave
  = mouseFilter "leave" filter
  where
    filter (MouseLeave point mod)  = True
    filter other                   = False
mouseFilter :: Reactive w => String -> (EventMouse -> Bool) -> Event w (Point -> IO ())
mouseFilter name filter
  = mapEvent get set mouse
  where
    get prev x
      = ioError (userError ("WX.Events: the " ++ name ++ " event is write-only."))
    set prev new mouseEvent
      = if (filter mouseEvent) 
         then new (mousePos mouseEvent)
         else prev mouseEvent
rebind :: Event w (IO ()) -> Event w (IO ())
rebind event
  = mapEvent get set event
  where
    get prev
      = prev
    set new prev
      = new
enterKey,tabKey,escKey,helpKey,delKey,homeKey,endKey :: Reactive w => Event w (IO ())
pgupKey,pgdownKey,downKey,upKey,leftKey,rightKey :: Reactive w => Event w (IO ())
enterKey  = key KeyReturn
tabKey    = key KeyTab
escKey    = key KeyEscape
helpKey   = key KeyHelp
delKey    = key KeyDelete
homeKey   = key KeyHome
endKey    = key KeyEnd
pgupKey   = key KeyPageUp
pgdownKey = key KeyPageDown
downKey   = key KeyDown
upKey     = key KeyUp
leftKey   = key KeyLeft
rightKey  = key KeyRight
charKey :: Reactive w => Char -> Event w (IO ())
charKey c
  = key (KeyChar c)
key :: Reactive w => Key -> Event w (IO ())
key k
  = keyboardFilter "key" filter
  where
    filter (EventKey x mod pt)  = k==x
anyKey :: Reactive w => Event w (Key -> IO ())
anyKey
  = keyboardFilter1 "anyKey" (const True)
keyboardFilter :: Reactive w => String -> (EventKey -> Bool) -> Event w (IO ())
keyboardFilter name filter
  = mapEvent get set keyboard
  where
    get prev
      = ioError (userError ("WX.Events: the " ++ name ++ " event is write-only."))
    set prev new keyboardEvent
      = do when (filter keyboardEvent) new
           prev keyboardEvent
keyboardFilter1 :: Reactive w => String -> (EventKey -> Bool) -> Event w (Key -> IO ())
keyboardFilter1 name filter
  = mapEvent get set keyboard
  where
    get prev key
      = ioError (userError ("WX.Events: the " ++ name ++ " event is write-only."))
    set prev new keyboardEvent
      = if (filter keyboardEvent) 
         then new (keyKey keyboardEvent)
         else prev keyboardEvent
calendarEvent :: Event (CalendarCtrl a) (EventCalendar -> IO ())
calendarEvent
  = newEvent "calendarEvent" calendarCtrlGetOnCalEvent calendarCtrlOnCalEvent
newEvent :: String -> (w -> IO a) -> (w -> a -> IO ()) -> Event w a
newEvent name getter setter
  = Event (newAttr name getter setter)