module Eventloop.Types.EventTypes where import System.IO import Data.Maybe import Control.Concurrent import qualified Eventloop.Utility.Websockets as WS import qualified Eventloop.Utility.BufferedWebsockets as BWS import Eventloop.Utility.Concurrent import Eventloop.Module.Websocket.Keyboard.Types import Eventloop.Module.Websocket.Mouse.Types import Eventloop.Module.Websocket.Canvas.Types import Eventloop.Module.DrawTrees.Types import Eventloop.Module.BasicShapes.Types import Eventloop.Module.File.Types import Eventloop.Module.StdIn.Types import Eventloop.Module.StdOut.Types import Eventloop.Module.Timer.Types import Eventloop.Module.Graphs.Types -- General Types type EventloopModuleIdentifier = [Char] type Initializer = SharedIOState -> IOState -> IO (SharedIOState, IOState) type EventRetriever = SharedIOState -> IOState -> IO (SharedIOState, IOState, [In]) type PreProcessor = SharedIOState -> IOState -> In -> IO (SharedIOState, IOState, [In]) type PostProcessor = SharedIOState -> IOState -> Out -> IO (SharedIOState, IOState, [Out]) type EventSender = SharedIOState -> IOState -> Out -> IO (SharedIOState, IOState) type Teardown = SharedIOState -> IOState -> IO (SharedIOState, IOState) type OutEventRouter = Out -> EventloopModuleIdentifier data EventloopModuleConfiguration = EventloopModuleConfiguration { moduleIdentifier :: EventloopModuleIdentifier , iostate :: IOState , initializer :: Maybe Initializer , eventRetriever :: Maybe EventRetriever , preprocessor :: Maybe PreProcessor , postprocessor :: Maybe PostProcessor , teardown :: Maybe Teardown , eventSender :: Maybe EventSender } data EventloopConfiguration progstateT = EventloopConfiguration { progState :: progstateT , eventloopFunc :: progstateT -> In -> (progstateT, [Out]) , outRouter :: OutEventRouter , sharedIOState :: SharedIOState , moduleConfigurations :: [EventloopModuleConfiguration] } data In = Start | InKeyboard Keyboard | InMouse MouseIn | InFile FileIn | InTimer TimerIn | InStdIn StdInIn | InCanvas CanvasIn | InGraphs GraphsIn deriving (Eq, Show) data Out = OutFile FileOut | OutTimer TimerOut | OutStdOut StdOutOut | OutStdIn StdInOut | OutCanvas CanvasOut | OutBasicShapes BasicShapesOut | OutDrawTrees DrawTreesOut | OutGraphs GraphsOut | Stop deriving (Eq, Show) -- Shared IO State data SharedIOState = SharedIOState { measureText :: CanvasText -> IO ScreenDimensions } -- Modules IO State data IOState = MouseState { receiveBuffer :: BWS.BufferedReceiveBuffer , clientSocket :: BWS.ClientSocket , clientConnection :: BWS.Connection , serverSocket :: BWS.ServerSocket , bufferedReaderThread :: BWS.BufferedReaderThread } | KeyboardState { receiveBuffer :: BWS.BufferedReceiveBuffer , clientSocket :: BWS.ClientSocket , clientConnection :: BWS.Connection , serverSocket :: BWS.ServerSocket , bufferedReaderThread :: BWS.BufferedReaderThread } | CanvasState { commonReceiveBuffer :: WS.ReceiveBuffer , canvasUserReceiveBuffer :: CanvasUserReceiveBuffer , canvasSystemReceiveBuffer :: CanvasSystemReceiveBuffer , clientSocket :: WS.ClientSocket , clientConnection :: WS.Connection , serverSocket :: WS.ServerSocket , unbufferedReaderThread :: WS.UnbufferedReaderThread , routerThread :: Thread } | StdInState { newStdInInEvents :: [StdInIn] } | TimerState { startedIntervalTimers :: [StartedTimer] , startedTimers :: [StartedTimer] , incomingIntervalTickBuffer :: IncomingTickBuffer , incomingTickBuffer :: IncomingTickBuffer } | FileState { newFileInEvents :: [FileIn] , opened :: [OpenFile] } | NoState -- API module types type APIName = [Char] type Parameter = [Char] --type Value = [Char] --type Parameters =[(Parameter, Value)]