{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Bridge where
import Prelude
import Data.Data
import Data.Text (Text)
data EventHandler a
= OnKeyDown !a
| OnKeyUp !a
| OnKeyPress !a
| OnFocus !a
| OnBlur !a
| OnValueChange !a
| OnCheckedChange !a
| OnSelectedChange !a
| OnSubmit !a
| OnClick !a
| OnDoubleClick !a
| OnMouseDown !a
| OnMouseUp !a
| OnMouseMove !a
| OnMouseEnter !a
| OnMouseLeave !a
| OnMouseOver !a
| OnMouseOut !a
| OnScroll !a
| OnWheel !a
#ifdef FAY
deriving (Typeable, Data)
#else
deriving (Functor, Typeable, Data)
#endif
data In a = PingPong
| Send (Action a)
| AskEvents
deriving (Data, Typeable)
data Out a = EmptyCmd
| ExecuteClient ClientId (ClientTask a) ExecuteStrategy
deriving (Data, Typeable)
data ExecuteStrategy =
ExecuteAll | ExecuteExcept
deriving (Data, Typeable, Eq)
data ClientTask a = ClientTask
{ executeRenderHtml :: [RenderHtml]
, executeAction :: [CallbackAction a]
} deriving (Data, Typeable)
data RenderHtml = AttachText ElementId HtmlText
| AttachDOM ElementId HtmlText deriving (Data, Typeable)
data CallbackAction a = CallbackAction (EventHandler a)
#ifdef FAY
deriving (Typeable, Data)
#else
deriving (Typeable, Data)
instance Show a => Show (CallbackAction a) where
show = show
#endif
data Action a = Action ElementId ActionType a
#ifdef FAY
deriving (Typeable, Data)
#else
deriving (Show, Typeable, Data)
#endif
data ActionType = RecordAction | ObjectAction
#ifdef FAY
deriving (Typeable, Data)
#else
deriving (Show, Typeable, Data)
#endif
type ElementId = Text
type HtmlText = Text
type ObjectId = Int
type AttrId = Int
type ClientId = Int
type RowNumber = Int
type RecordValue = Text
ppIncomingCommand :: In a -> Text
ppIncomingCommand AskEvents = "AskEvents"
ppIncomingCommand (Send _) = "SendObjectAction"
ppIncomingCommand PingPong = "PingPong"