module FPPrac.Events
( FileType (..)
, Input (..)
, Output (..)
, PanelItemType (..)
, PromptInfo
, PanelContent
, PanelItem
, installEventHandler
)
where
import Data.List (mapAccumL)
import FPPrac.Graphics
import FPPrac.GUI.Panel
import FPPrac.GUI.Prompt
import Graphics.Gloss.Interface.Pure.Game hiding (play)
import Graphics.Gloss.Interface.IO.Game (playIO)
import Data.Time (getCurrentTime,utctDayTime)
import Control.Exception as X
type PromptInfo = (String,String)
data FileType
= TXTFile String
| BMPFile Picture
deriving (Eq,Show)
data Input
= NoInput
| KeyIn Char
| MouseDown (Float,Float)
| MouseUp (Float,Float)
| MouseMotion (Float,Float)
| MouseDoubleClick (Float,Float)
| Prompt PromptInfo
| Panel Int [(Int,String)]
| File FilePath FileType
| Save FilePath Bool
| Time Float
| Invalid
deriving (Eq,Show)
data Output
= DrawOnBuffer Bool
| DrawPicture Picture
| GraphPrompt PromptInfo
| PanelCreate PanelContent
| PanelUpdate Bool [(Int,String)]
| ScreenClear
| ReadFile FilePath FileType
| SaveFile FilePath FileType
| GetTime
deriving (Eq,Show)
data GUIMode = PanelMode | PromptMode PromptInfo String | FreeMode | PerformIO
deriving (Eq,Show)
data EventState a = EventState { screen :: Picture
, buffer :: Picture
, drawOnBuffer :: Bool
, storedInputs :: [Input]
, storedOutputs :: [Output]
, doubleClickT :: Int
, guiMode :: GUIMode
, panel :: Maybe (PanelContent,[(Int,String)])
, userState :: a
}
eventToInput ::
Event
-> Input
eventToInput (EventKey (Char x) Down _ _) = KeyIn x
eventToInput (EventKey (SpecialKey KeySpace) Down _ _) = KeyIn ' '
eventToInput (EventKey (SpecialKey KeyTab) Down _ _) = KeyIn '\t'
eventToInput (EventKey (SpecialKey KeyEnter) Down _ _) = KeyIn '\n'
eventToInput (EventKey (SpecialKey KeyBackspace) Down _ _) = KeyIn '\b'
eventToInput (EventKey (MouseButton LeftButton) Down _ p) = MouseDown p
eventToInput (EventKey (MouseButton LeftButton) Up _ p) = MouseUp p
eventToInput (EventMotion p) = MouseMotion p
eventToInput _ = Invalid
installEventHandler ::
forall userState
. String
-> (userState -> Input -> (userState, [Output]))
-> userState
-> Picture
-> Int
-> IO ()
installEventHandler name handler initState p dcTime = playIO
(InWindow name (800,600) (20,20))
white
50
(EventState p p True [] [] 0 FreeMode Nothing initState)
(return . screen)
(\e s -> handleInputIO handler dcTime s (eventToInput e))
(\_ s -> handleInputIO handler dcTime s NoInput)
handleInputIO ::
forall userState
. (userState -> Input -> (userState, [Output]))
-> Int
-> EventState userState
-> Input
-> IO (EventState userState)
handleInputIO handler dcTime s@(EventState {guiMode = PerformIO,..}) i = do
inps <- fmap (filter (/= Invalid)) $ mapM handleIO storedOutputs
let s' = s {guiMode = FreeMode, storedOutputs = [], storedInputs = storedInputs ++ inps}
return $ handleInput handler dcTime s' i
handleInputIO handler dcTime s i = return $ handleInput handler dcTime s i
handleInput ::
forall userState
. (userState -> Input -> (userState, [Output]))
-> Int
-> EventState userState
-> Input
-> EventState userState
handleInput handler dcTime s@(EventState {guiMode = FreeMode, ..}) i
= s' {userState = userState', doubleClickT = doubleClickT', storedInputs = []}
where
(doubleClickT',dc) = registerDoubleClick dcTime doubleClickT i
remainingInputs = storedInputs ++ (if null dc then [i] else dc)
(userState',outps) = mapAccumL handler userState remainingInputs
s' = foldl handleOutput s $ concat outps
handleInput handler _ s@(EventState {guiMode = PanelMode, panel = Just (panelContents,itemState), ..}) (MouseDown (x,y))
| isClicked /= Nothing = s''
| otherwise = s
where
isClicked = onItem panelContents (x,y)
(Just itemClicked) = isClicked
itemState' = toggleItem itemState itemClicked
(userState',outps) = handler userState (Panel (fst itemClicked) $ filter ((/= "") . snd) itemState')
s' = s {screen = Pictures [buffer,drawPanel panelContents itemState'], panel = Just (panelContents,itemState'), userState = userState'}
s'' = foldl handleOutput s' outps
handleInput _ _ s@(EventState {guiMode = PromptMode pInfo pContent, ..}) (KeyIn '\b')
| pContent /= [] = s'
| otherwise = s
where
pContent' = init pContent
screen' = Pictures [buffer,drawPrompt pInfo pContent']
s' = s {guiMode = PromptMode pInfo pContent', screen = screen'}
handleInput handler _ s@(EventState {guiMode = PromptMode (pName,_) pContent, ..}) (KeyIn '\n')
= s''
where
(userState',outps) = handler userState (Prompt (pName,pContent))
s' = s {guiMode = FreeMode, screen = buffer, userState = userState'}
s'' = foldl handleOutput s' outps
handleInput _ _ s@(EventState {guiMode = PromptMode pInfo pContent, ..}) (KeyIn x)
= s'
where
pContent' = pContent ++ [x]
screen' = Pictures [buffer,drawPrompt pInfo pContent']
s' = s {guiMode = PromptMode pInfo pContent', screen = screen'}
handleInput _ _ s _ = s
registerDoubleClick ::
Int
-> Int
-> Input
-> (Int,[Input])
registerDoubleClick d 0 (MouseDown _) = (d ,[])
registerDoubleClick _ _ (MouseDown (x,y)) = (0 ,[MouseDoubleClick (x,y)])
registerDoubleClick _ 0 NoInput = (0 ,[])
registerDoubleClick _ n NoInput = (n1,[])
registerDoubleClick _ n _ = (n ,[])
handleOutput ::
EventState a
-> Output
-> EventState a
handleOutput s (DrawOnBuffer b) = s {drawOnBuffer = b}
handleOutput s ScreenClear = s {buffer = Blank, screen = Blank}
handleOutput s@(EventState {..}) (DrawPicture p) =
s { buffer = if drawOnBuffer
then Pictures [buffer, p]
else buffer
, screen = Pictures [buffer, p]
}
handleOutput s@(EventState {guiMode = FreeMode, ..}) i@(ReadFile _ _) =
s {guiMode = PerformIO, storedOutputs = storedOutputs ++ [i]}
handleOutput s@(EventState {guiMode = FreeMode, ..}) i@(SaveFile _ _) =
s {guiMode = PerformIO, storedOutputs = storedOutputs ++ [i]}
handleOutput s@(EventState {guiMode = FreeMode, ..}) i@(GetTime) =
s {guiMode = PerformIO, storedOutputs = storedOutputs ++ [i]}
handleOutput s@(EventState {..}) (PanelCreate panelContent)
= s {panel = Just (panelContent,defItemState)}
where
defItemState = createDefState panelContent
handleOutput s@(EventState {panel = Just (panelContents,itemState), ..}) (PanelUpdate True _)
= s {guiMode = PanelMode, screen = Pictures [buffer,drawPanel panelContents itemState]}
handleOutput s@(EventState {panel = Nothing}) (PanelUpdate True _)
= s
handleOutput s@(EventState {panel = Just (panelContents,_), ..}) (PanelUpdate False _)
= s {guiMode = FreeMode, screen = buffer, panel = Just (panelContents,defItemState)}
where
defItemState = createDefState panelContents
handleOutput s@(EventState {panel = Nothing, ..}) (PanelUpdate False _)
= s {guiMode = FreeMode, screen = buffer}
handleOutput s@(EventState {..}) (GraphPrompt promptInfo)
= s {guiMode = PromptMode promptInfo "", screen = Pictures [buffer,drawPrompt promptInfo ""]}
handleOutput s _ = s
handleIO :: Output -> IO Input
handleIO (ReadFile filePath (TXTFile defContents)) =
(do f <- readFile filePath
return $ File filePath $ TXTFile f
) `X.catch`
(\(_ :: IOException) -> return (File filePath $ TXTFile defContents))
handleIO (ReadFile filePath (BMPFile defContents)) =
(do f <- loadBMP filePath
return $ File filePath $ BMPFile f
) `X.catch`
(\(_ :: IOException) -> return (File filePath $ BMPFile defContents))
handleIO (SaveFile filePath (TXTFile content)) =
( do writeFile filePath content
return $ Save filePath True
) `X.catch`
(\(_ :: IOException) -> return $ Save filePath False)
handleIO (SaveFile filePath (BMPFile _)) = return $ Save filePath False
handleIO GetTime = do
t <- fmap utctDayTime $ getCurrentTime
return $ Time (fromRational $ toRational t)
handleIO _ = return Invalid