{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
module Monomer.Core.WidgetTypes where
import Control.Concurrent (MVar)
import Control.Lens (ALens')
import Data.ByteString.Lazy (ByteString)
import Data.Default
import Data.Map.Strict (Map)
import Data.Sequence (Seq)
import Data.String (IsString(..))
import Data.Text (Text)
import Data.Typeable (Typeable, typeOf)
import GHC.Generics
import qualified Data.Text as T
import Monomer.Common
import Monomer.Core.StyleTypes
import Monomer.Core.ThemeTypes
import Monomer.Event.Types
import Monomer.Graphics.Types
type Timestamp = Int
type WidgetModel s = Typeable s
type WidgetEvent e = Typeable e
type WidgetKeyMap s e = Map WidgetKey (WidgetNode s e)
data FocusDirection
= FocusFwd
| FocusBwd
deriving (FocusDirection -> FocusDirection -> Bool
(FocusDirection -> FocusDirection -> Bool)
-> (FocusDirection -> FocusDirection -> Bool) -> Eq FocusDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FocusDirection -> FocusDirection -> Bool
$c/= :: FocusDirection -> FocusDirection -> Bool
== :: FocusDirection -> FocusDirection -> Bool
$c== :: FocusDirection -> FocusDirection -> Bool
Eq, Int -> FocusDirection -> ShowS
[FocusDirection] -> ShowS
FocusDirection -> String
(Int -> FocusDirection -> ShowS)
-> (FocusDirection -> String)
-> ([FocusDirection] -> ShowS)
-> Show FocusDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FocusDirection] -> ShowS
$cshowList :: [FocusDirection] -> ShowS
show :: FocusDirection -> String
$cshow :: FocusDirection -> String
showsPrec :: Int -> FocusDirection -> ShowS
$cshowsPrec :: Int -> FocusDirection -> ShowS
Show)
data WindowRequest
= WindowSetTitle Text
| WindowSetFullScreen
| WindowMaximize
| WindowMinimize
| WindowRestore
| WindowBringToFront
deriving (WindowRequest -> WindowRequest -> Bool
(WindowRequest -> WindowRequest -> Bool)
-> (WindowRequest -> WindowRequest -> Bool) -> Eq WindowRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowRequest -> WindowRequest -> Bool
$c/= :: WindowRequest -> WindowRequest -> Bool
== :: WindowRequest -> WindowRequest -> Bool
$c== :: WindowRequest -> WindowRequest -> Bool
Eq, Int -> WindowRequest -> ShowS
[WindowRequest] -> ShowS
WindowRequest -> String
(Int -> WindowRequest -> ShowS)
-> (WindowRequest -> String)
-> ([WindowRequest] -> ShowS)
-> Show WindowRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowRequest] -> ShowS
$cshowList :: [WindowRequest] -> ShowS
show :: WindowRequest -> String
$cshow :: WindowRequest -> String
showsPrec :: Int -> WindowRequest -> ShowS
$cshowsPrec :: Int -> WindowRequest -> ShowS
Show)
newtype WidgetType
= WidgetType Text
deriving (WidgetType -> WidgetType -> Bool
(WidgetType -> WidgetType -> Bool)
-> (WidgetType -> WidgetType -> Bool) -> Eq WidgetType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetType -> WidgetType -> Bool
$c/= :: WidgetType -> WidgetType -> Bool
== :: WidgetType -> WidgetType -> Bool
$c== :: WidgetType -> WidgetType -> Bool
Eq, Int -> WidgetType -> ShowS
[WidgetType] -> ShowS
WidgetType -> String
(Int -> WidgetType -> ShowS)
-> (WidgetType -> String)
-> ([WidgetType] -> ShowS)
-> Show WidgetType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetType] -> ShowS
$cshowList :: [WidgetType] -> ShowS
show :: WidgetType -> String
$cshow :: WidgetType -> String
showsPrec :: Int -> WidgetType -> ShowS
$cshowsPrec :: Int -> WidgetType -> ShowS
Show, (forall x. WidgetType -> Rep WidgetType x)
-> (forall x. Rep WidgetType x -> WidgetType) -> Generic WidgetType
forall x. Rep WidgetType x -> WidgetType
forall x. WidgetType -> Rep WidgetType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetType x -> WidgetType
$cfrom :: forall x. WidgetType -> Rep WidgetType x
Generic)
instance IsString WidgetType where
fromString :: String -> WidgetType
fromString = Text -> WidgetType
WidgetType (Text -> WidgetType) -> (String -> Text) -> String -> WidgetType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
data WidgetData s a
= WidgetValue a
| WidgetLens (ALens' s a)
data WidgetId = WidgetId {
WidgetId -> Int
_widTs :: Int,
WidgetId -> Path
_widPath :: Path
} deriving (WidgetId -> WidgetId -> Bool
(WidgetId -> WidgetId -> Bool)
-> (WidgetId -> WidgetId -> Bool) -> Eq WidgetId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetId -> WidgetId -> Bool
$c/= :: WidgetId -> WidgetId -> Bool
== :: WidgetId -> WidgetId -> Bool
$c== :: WidgetId -> WidgetId -> Bool
Eq, Int -> WidgetId -> ShowS
[WidgetId] -> ShowS
WidgetId -> String
(Int -> WidgetId -> ShowS)
-> (WidgetId -> String) -> ([WidgetId] -> ShowS) -> Show WidgetId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetId] -> ShowS
$cshowList :: [WidgetId] -> ShowS
show :: WidgetId -> String
$cshow :: WidgetId -> String
showsPrec :: Int -> WidgetId -> ShowS
$cshowsPrec :: Int -> WidgetId -> ShowS
Show, Eq WidgetId
Eq WidgetId
-> (WidgetId -> WidgetId -> Ordering)
-> (WidgetId -> WidgetId -> Bool)
-> (WidgetId -> WidgetId -> Bool)
-> (WidgetId -> WidgetId -> Bool)
-> (WidgetId -> WidgetId -> Bool)
-> (WidgetId -> WidgetId -> WidgetId)
-> (WidgetId -> WidgetId -> WidgetId)
-> Ord WidgetId
WidgetId -> WidgetId -> Bool
WidgetId -> WidgetId -> Ordering
WidgetId -> WidgetId -> WidgetId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WidgetId -> WidgetId -> WidgetId
$cmin :: WidgetId -> WidgetId -> WidgetId
max :: WidgetId -> WidgetId -> WidgetId
$cmax :: WidgetId -> WidgetId -> WidgetId
>= :: WidgetId -> WidgetId -> Bool
$c>= :: WidgetId -> WidgetId -> Bool
> :: WidgetId -> WidgetId -> Bool
$c> :: WidgetId -> WidgetId -> Bool
<= :: WidgetId -> WidgetId -> Bool
$c<= :: WidgetId -> WidgetId -> Bool
< :: WidgetId -> WidgetId -> Bool
$c< :: WidgetId -> WidgetId -> Bool
compare :: WidgetId -> WidgetId -> Ordering
$ccompare :: WidgetId -> WidgetId -> Ordering
$cp1Ord :: Eq WidgetId
Ord, (forall x. WidgetId -> Rep WidgetId x)
-> (forall x. Rep WidgetId x -> WidgetId) -> Generic WidgetId
forall x. Rep WidgetId x -> WidgetId
forall x. WidgetId -> Rep WidgetId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetId x -> WidgetId
$cfrom :: forall x. WidgetId -> Rep WidgetId x
Generic)
instance Default WidgetId where
def :: WidgetId
def = Int -> Path -> WidgetId
WidgetId Int
0 Path
emptyPath
newtype WidgetKey
= WidgetKey Text
deriving (WidgetKey -> WidgetKey -> Bool
(WidgetKey -> WidgetKey -> Bool)
-> (WidgetKey -> WidgetKey -> Bool) -> Eq WidgetKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetKey -> WidgetKey -> Bool
$c/= :: WidgetKey -> WidgetKey -> Bool
== :: WidgetKey -> WidgetKey -> Bool
$c== :: WidgetKey -> WidgetKey -> Bool
Eq, Int -> WidgetKey -> ShowS
[WidgetKey] -> ShowS
WidgetKey -> String
(Int -> WidgetKey -> ShowS)
-> (WidgetKey -> String)
-> ([WidgetKey] -> ShowS)
-> Show WidgetKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetKey] -> ShowS
$cshowList :: [WidgetKey] -> ShowS
show :: WidgetKey -> String
$cshow :: WidgetKey -> String
showsPrec :: Int -> WidgetKey -> ShowS
$cshowsPrec :: Int -> WidgetKey -> ShowS
Show, Eq WidgetKey
Eq WidgetKey
-> (WidgetKey -> WidgetKey -> Ordering)
-> (WidgetKey -> WidgetKey -> Bool)
-> (WidgetKey -> WidgetKey -> Bool)
-> (WidgetKey -> WidgetKey -> Bool)
-> (WidgetKey -> WidgetKey -> Bool)
-> (WidgetKey -> WidgetKey -> WidgetKey)
-> (WidgetKey -> WidgetKey -> WidgetKey)
-> Ord WidgetKey
WidgetKey -> WidgetKey -> Bool
WidgetKey -> WidgetKey -> Ordering
WidgetKey -> WidgetKey -> WidgetKey
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WidgetKey -> WidgetKey -> WidgetKey
$cmin :: WidgetKey -> WidgetKey -> WidgetKey
max :: WidgetKey -> WidgetKey -> WidgetKey
$cmax :: WidgetKey -> WidgetKey -> WidgetKey
>= :: WidgetKey -> WidgetKey -> Bool
$c>= :: WidgetKey -> WidgetKey -> Bool
> :: WidgetKey -> WidgetKey -> Bool
$c> :: WidgetKey -> WidgetKey -> Bool
<= :: WidgetKey -> WidgetKey -> Bool
$c<= :: WidgetKey -> WidgetKey -> Bool
< :: WidgetKey -> WidgetKey -> Bool
$c< :: WidgetKey -> WidgetKey -> Bool
compare :: WidgetKey -> WidgetKey -> Ordering
$ccompare :: WidgetKey -> WidgetKey -> Ordering
$cp1Ord :: Eq WidgetKey
Ord, (forall x. WidgetKey -> Rep WidgetKey x)
-> (forall x. Rep WidgetKey x -> WidgetKey) -> Generic WidgetKey
forall x. Rep WidgetKey x -> WidgetKey
forall x. WidgetKey -> Rep WidgetKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetKey x -> WidgetKey
$cfrom :: forall x. WidgetKey -> Rep WidgetKey x
Generic)
instance IsString WidgetKey where
fromString :: String -> WidgetKey
fromString = Text -> WidgetKey
WidgetKey (Text -> WidgetKey) -> (String -> Text) -> String -> WidgetKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
data WidgetState
= forall i . WidgetModel i => WidgetState i
instance Show WidgetState where
show :: WidgetState -> String
show (WidgetState i
state) = String
"WidgetState: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (i -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf i
state)
data WidgetShared
= forall i . Typeable i => WidgetShared i
instance Show WidgetShared where
show :: WidgetShared -> String
show (WidgetShared i
shared) = String
"WidgetShared: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ TypeRep -> String
forall a. Show a => a -> String
show (i -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf i
shared)
data WidgetRequest s e
= IgnoreParentEvents
| IgnoreChildrenEvents
| ResizeWidgets WidgetId
| ResizeWidgetsImmediate WidgetId
| MoveFocus (Maybe WidgetId) FocusDirection
| SetFocus WidgetId
| GetClipboard WidgetId
| SetClipboard ClipboardData
| StartTextInput Rect
| StopTextInput
| SetOverlay WidgetId Path
| ResetOverlay WidgetId
| SetCursorIcon WidgetId CursorIcon
| ResetCursorIcon WidgetId
| StartDrag WidgetId Path WidgetDragMsg
| StopDrag WidgetId
| RenderOnce
| RenderEvery WidgetId Int (Maybe Int)
| RenderStop WidgetId
| RemoveRendererImage Text
| ExitApplication Bool
| UpdateWindow WindowRequest
| UpdateModel (s -> s)
| SetWidgetPath WidgetId Path
| ResetWidgetPath WidgetId
| WidgetEvent e => RaiseEvent e
| forall i . Typeable i => SendMessage WidgetId i
| forall i . Typeable i => RunTask WidgetId Path (IO i)
| forall i . Typeable i => RunProducer WidgetId Path ((i -> IO ()) -> IO ())
instance Eq e => Eq (WidgetRequest s e) where
WidgetRequest s e
IgnoreParentEvents == :: WidgetRequest s e -> WidgetRequest s e -> Bool
== WidgetRequest s e
IgnoreParentEvents = Bool
True
WidgetRequest s e
IgnoreChildrenEvents == WidgetRequest s e
IgnoreChildrenEvents = Bool
True
ResizeWidgets WidgetId
w1 == ResizeWidgets WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
ResizeWidgetsImmediate WidgetId
w1 == ResizeWidgetsImmediate WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
MoveFocus Maybe WidgetId
w1 FocusDirection
fd1 == MoveFocus Maybe WidgetId
w2 FocusDirection
fd2 = (Maybe WidgetId
w1, FocusDirection
fd1) (Maybe WidgetId, FocusDirection)
-> (Maybe WidgetId, FocusDirection) -> Bool
forall a. Eq a => a -> a -> Bool
== (Maybe WidgetId
w2, FocusDirection
fd2)
SetFocus WidgetId
w1 == SetFocus WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
GetClipboard WidgetId
w1 == GetClipboard WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
SetClipboard ClipboardData
c1 == SetClipboard ClipboardData
c2 = ClipboardData
c1 ClipboardData -> ClipboardData -> Bool
forall a. Eq a => a -> a -> Bool
== ClipboardData
c2
StartTextInput Rect
r1 == StartTextInput Rect
r2 = Rect
r1 Rect -> Rect -> Bool
forall a. Eq a => a -> a -> Bool
== Rect
r2
WidgetRequest s e
StopTextInput == WidgetRequest s e
StopTextInput = Bool
True
SetOverlay WidgetId
w1 Path
p1 == SetOverlay WidgetId
w2 Path
p2 = (WidgetId
w1, Path
p1) (WidgetId, Path) -> (WidgetId, Path) -> Bool
forall a. Eq a => a -> a -> Bool
== (WidgetId
w2, Path
p2)
ResetOverlay WidgetId
w1 == ResetOverlay WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
SetCursorIcon WidgetId
w1 CursorIcon
c1 == SetCursorIcon WidgetId
w2 CursorIcon
c2 = (WidgetId
w1, CursorIcon
c1) (WidgetId, CursorIcon) -> (WidgetId, CursorIcon) -> Bool
forall a. Eq a => a -> a -> Bool
== (WidgetId
w2, CursorIcon
c2)
ResetCursorIcon WidgetId
w1 == ResetCursorIcon WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
StartDrag WidgetId
w1 Path
p1 WidgetDragMsg
m1 == StartDrag WidgetId
w2 Path
p2 WidgetDragMsg
m2 = (WidgetId
w1, Path
p1, WidgetDragMsg
m1) (WidgetId, Path, WidgetDragMsg)
-> (WidgetId, Path, WidgetDragMsg) -> Bool
forall a. Eq a => a -> a -> Bool
== (WidgetId
w2, Path
p2, WidgetDragMsg
m2)
StopDrag WidgetId
w1 == StopDrag WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
WidgetRequest s e
RenderOnce == WidgetRequest s e
RenderOnce = Bool
True
RenderEvery WidgetId
p1 Int
c1 Maybe Int
r1 == RenderEvery WidgetId
p2 Int
c2 Maybe Int
r2 = (WidgetId
p1, Int
c1, Maybe Int
r1) (WidgetId, Int, Maybe Int) -> (WidgetId, Int, Maybe Int) -> Bool
forall a. Eq a => a -> a -> Bool
== (WidgetId
p2, Int
c2, Maybe Int
r2)
RenderStop WidgetId
p1 == RenderStop WidgetId
p2 = WidgetId
p1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
p2
ExitApplication Bool
e1 == ExitApplication Bool
e2 = Bool
e1 Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
e2
UpdateWindow WindowRequest
w1 == UpdateWindow WindowRequest
w2 = WindowRequest
w1 WindowRequest -> WindowRequest -> Bool
forall a. Eq a => a -> a -> Bool
== WindowRequest
w2
SetWidgetPath WidgetId
w1 Path
p1 == SetWidgetPath WidgetId
w2 Path
p2 = (WidgetId
w1, Path
p1) (WidgetId, Path) -> (WidgetId, Path) -> Bool
forall a. Eq a => a -> a -> Bool
== (WidgetId
w2, Path
p2)
ResetWidgetPath WidgetId
w1 == ResetWidgetPath WidgetId
w2 = WidgetId
w1 WidgetId -> WidgetId -> Bool
forall a. Eq a => a -> a -> Bool
== WidgetId
w2
RaiseEvent e
e1 == RaiseEvent e
e2 = e
e1 e -> e -> Bool
forall a. Eq a => a -> a -> Bool
== e
e2
WidgetRequest s e
_ == WidgetRequest s e
_ = Bool
False
data WidgetResult s e = WidgetResult {
WidgetResult s e -> WidgetNode s e
_wrNode :: WidgetNode s e,
WidgetResult s e -> Seq (WidgetRequest s e)
_wrRequests :: Seq (WidgetRequest s e)
}
instance Semigroup (WidgetResult s e) where
WidgetResult s e
er1 <> :: WidgetResult s e -> WidgetResult s e -> WidgetResult s e
<> WidgetResult s e
er2 = WidgetResult :: forall s e.
WidgetNode s e -> Seq (WidgetRequest s e) -> WidgetResult s e
WidgetResult {
_wrNode :: WidgetNode s e
_wrNode = WidgetResult s e -> WidgetNode s e
forall s e. WidgetResult s e -> WidgetNode s e
_wrNode WidgetResult s e
er2,
_wrRequests :: Seq (WidgetRequest s e)
_wrRequests = WidgetResult s e -> Seq (WidgetRequest s e)
forall s e. WidgetResult s e -> Seq (WidgetRequest s e)
_wrRequests WidgetResult s e
er1 Seq (WidgetRequest s e)
-> Seq (WidgetRequest s e) -> Seq (WidgetRequest s e)
forall a. Semigroup a => a -> a -> a
<> WidgetResult s e -> Seq (WidgetRequest s e)
forall s e. WidgetResult s e -> Seq (WidgetRequest s e)
_wrRequests WidgetResult s e
er2
}
data LayoutDirection
= LayoutNone
| LayoutHorizontal
| LayoutVertical
deriving (LayoutDirection -> LayoutDirection -> Bool
(LayoutDirection -> LayoutDirection -> Bool)
-> (LayoutDirection -> LayoutDirection -> Bool)
-> Eq LayoutDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutDirection -> LayoutDirection -> Bool
$c/= :: LayoutDirection -> LayoutDirection -> Bool
== :: LayoutDirection -> LayoutDirection -> Bool
$c== :: LayoutDirection -> LayoutDirection -> Bool
Eq, Int -> LayoutDirection -> ShowS
[LayoutDirection] -> ShowS
LayoutDirection -> String
(Int -> LayoutDirection -> ShowS)
-> (LayoutDirection -> String)
-> ([LayoutDirection] -> ShowS)
-> Show LayoutDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LayoutDirection] -> ShowS
$cshowList :: [LayoutDirection] -> ShowS
show :: LayoutDirection -> String
$cshow :: LayoutDirection -> String
showsPrec :: Int -> LayoutDirection -> ShowS
$cshowsPrec :: Int -> LayoutDirection -> ShowS
Show, (forall x. LayoutDirection -> Rep LayoutDirection x)
-> (forall x. Rep LayoutDirection x -> LayoutDirection)
-> Generic LayoutDirection
forall x. Rep LayoutDirection x -> LayoutDirection
forall x. LayoutDirection -> Rep LayoutDirection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LayoutDirection x -> LayoutDirection
$cfrom :: forall x. LayoutDirection -> Rep LayoutDirection x
Generic)
data WidgetEnv s e = WidgetEnv {
WidgetEnv s e -> Text
_weOs :: Text,
WidgetEnv s e -> FontManager
_weFontManager :: FontManager,
WidgetEnv s e -> Path -> Maybe WidgetNodeInfo
_weFindByPath :: Path -> Maybe WidgetNodeInfo,
WidgetEnv s e -> Button
_weMainButton :: Button,
WidgetEnv s e -> Button
_weContextButton :: Button,
WidgetEnv s e -> Theme
_weTheme :: Theme,
WidgetEnv s e -> Size
_weWindowSize :: Size,
WidgetEnv s e -> MVar (Map Text WidgetShared)
_weWidgetShared :: MVar (Map Text WidgetShared),
WidgetEnv s e -> WidgetKeyMap s e
_weWidgetKeyMap :: WidgetKeyMap s e,
WidgetEnv s e -> Maybe Path
_weHoveredPath :: Maybe Path,
WidgetEnv s e -> Path
_weFocusedPath :: Path,
WidgetEnv s e -> Maybe Path
_weOverlayPath :: Maybe Path,
WidgetEnv s e -> Maybe (Path, WidgetDragMsg)
_weDragStatus :: Maybe (Path, WidgetDragMsg),
WidgetEnv s e -> Maybe (Path, Point)
_weMainBtnPress :: Maybe (Path, Point),
WidgetEnv s e -> Maybe (Path, CursorIcon)
_weCursor :: Maybe (Path, CursorIcon),
WidgetEnv s e -> s
_weModel :: s,
WidgetEnv s e -> InputStatus
_weInputStatus :: InputStatus,
WidgetEnv s e -> Int
_weTimestamp :: Timestamp,
WidgetEnv s e -> Bool
_weThemeChanged :: Bool,
WidgetEnv s e -> Point -> Bool
_weInTopLayer :: Point -> Bool,
WidgetEnv s e -> LayoutDirection
_weLayoutDirection :: LayoutDirection,
WidgetEnv s e -> Rect
_weViewport :: Rect,
WidgetEnv s e -> Point
_weOffset :: Point
}
data WidgetNodeInfo =
WidgetNodeInfo {
WidgetNodeInfo -> WidgetType
_wniWidgetType :: !WidgetType,
WidgetNodeInfo -> WidgetId
_wniWidgetId :: !WidgetId,
WidgetNodeInfo -> Maybe WidgetKey
_wniKey :: Maybe WidgetKey,
WidgetNodeInfo -> Path
_wniPath :: !Path,
WidgetNodeInfo -> SizeReq
_wniSizeReqW :: !SizeReq,
WidgetNodeInfo -> SizeReq
_wniSizeReqH :: !SizeReq,
WidgetNodeInfo -> Bool
_wniEnabled :: !Bool,
WidgetNodeInfo -> Bool
_wniVisible :: !Bool,
WidgetNodeInfo -> Bool
_wniFocusable :: !Bool,
WidgetNodeInfo -> Rect
_wniViewport :: !Rect,
WidgetNodeInfo -> Style
_wniStyle :: Style
} deriving (WidgetNodeInfo -> WidgetNodeInfo -> Bool
(WidgetNodeInfo -> WidgetNodeInfo -> Bool)
-> (WidgetNodeInfo -> WidgetNodeInfo -> Bool) -> Eq WidgetNodeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WidgetNodeInfo -> WidgetNodeInfo -> Bool
$c/= :: WidgetNodeInfo -> WidgetNodeInfo -> Bool
== :: WidgetNodeInfo -> WidgetNodeInfo -> Bool
$c== :: WidgetNodeInfo -> WidgetNodeInfo -> Bool
Eq, Int -> WidgetNodeInfo -> ShowS
[WidgetNodeInfo] -> ShowS
WidgetNodeInfo -> String
(Int -> WidgetNodeInfo -> ShowS)
-> (WidgetNodeInfo -> String)
-> ([WidgetNodeInfo] -> ShowS)
-> Show WidgetNodeInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetNodeInfo] -> ShowS
$cshowList :: [WidgetNodeInfo] -> ShowS
show :: WidgetNodeInfo -> String
$cshow :: WidgetNodeInfo -> String
showsPrec :: Int -> WidgetNodeInfo -> ShowS
$cshowsPrec :: Int -> WidgetNodeInfo -> ShowS
Show, (forall x. WidgetNodeInfo -> Rep WidgetNodeInfo x)
-> (forall x. Rep WidgetNodeInfo x -> WidgetNodeInfo)
-> Generic WidgetNodeInfo
forall x. Rep WidgetNodeInfo x -> WidgetNodeInfo
forall x. WidgetNodeInfo -> Rep WidgetNodeInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetNodeInfo x -> WidgetNodeInfo
$cfrom :: forall x. WidgetNodeInfo -> Rep WidgetNodeInfo x
Generic)
instance Default WidgetNodeInfo where
def :: WidgetNodeInfo
def = WidgetNodeInfo :: WidgetType
-> WidgetId
-> Maybe WidgetKey
-> Path
-> SizeReq
-> SizeReq
-> Bool
-> Bool
-> Bool
-> Rect
-> Style
-> WidgetNodeInfo
WidgetNodeInfo {
_wniWidgetType :: WidgetType
_wniWidgetType = Text -> WidgetType
WidgetType (String -> Text
T.pack String
""),
_wniWidgetId :: WidgetId
_wniWidgetId = WidgetId
forall a. Default a => a
def,
_wniKey :: Maybe WidgetKey
_wniKey = Maybe WidgetKey
forall a. Maybe a
Nothing,
_wniPath :: Path
_wniPath = Path
emptyPath,
_wniSizeReqW :: SizeReq
_wniSizeReqW = SizeReq
forall a. Default a => a
def,
_wniSizeReqH :: SizeReq
_wniSizeReqH = SizeReq
forall a. Default a => a
def,
_wniEnabled :: Bool
_wniEnabled = Bool
True,
_wniVisible :: Bool
_wniVisible = Bool
True,
_wniFocusable :: Bool
_wniFocusable = Bool
False,
_wniViewport :: Rect
_wniViewport = Rect
forall a. Default a => a
def,
_wniStyle :: Style
_wniStyle = Style
forall a. Default a => a
def
}
data WidgetNode s e = WidgetNode {
WidgetNode s e -> Widget s e
_wnWidget :: Widget s e,
WidgetNode s e -> WidgetNodeInfo
_wnInfo :: WidgetNodeInfo,
WidgetNode s e -> Seq (WidgetNode s e)
_wnChildren :: Seq (WidgetNode s e)
}
data WidgetInstanceNode = WidgetInstanceNode {
WidgetInstanceNode -> WidgetNodeInfo
_winInfo :: WidgetNodeInfo,
WidgetInstanceNode -> Maybe WidgetState
_winState :: Maybe WidgetState,
WidgetInstanceNode -> Seq WidgetInstanceNode
_winChildren :: Seq WidgetInstanceNode
} deriving (Int -> WidgetInstanceNode -> ShowS
[WidgetInstanceNode] -> ShowS
WidgetInstanceNode -> String
(Int -> WidgetInstanceNode -> ShowS)
-> (WidgetInstanceNode -> String)
-> ([WidgetInstanceNode] -> ShowS)
-> Show WidgetInstanceNode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WidgetInstanceNode] -> ShowS
$cshowList :: [WidgetInstanceNode] -> ShowS
show :: WidgetInstanceNode -> String
$cshow :: WidgetInstanceNode -> String
showsPrec :: Int -> WidgetInstanceNode -> ShowS
$cshowsPrec :: Int -> WidgetInstanceNode -> ShowS
Show, (forall x. WidgetInstanceNode -> Rep WidgetInstanceNode x)
-> (forall x. Rep WidgetInstanceNode x -> WidgetInstanceNode)
-> Generic WidgetInstanceNode
forall x. Rep WidgetInstanceNode x -> WidgetInstanceNode
forall x. WidgetInstanceNode -> Rep WidgetInstanceNode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WidgetInstanceNode x -> WidgetInstanceNode
$cfrom :: forall x. WidgetInstanceNode -> Rep WidgetInstanceNode x
Generic)
data Widget s e =
Widget {
Widget s e -> WidgetEnv s e -> WidgetNode s e -> WidgetResult s e
widgetInit
:: WidgetEnv s e
-> WidgetNode s e
-> WidgetResult s e,
Widget s e
-> WidgetEnv s e
-> WidgetNode s e
-> WidgetNode s e
-> WidgetResult s e
widgetMerge
:: WidgetEnv s e
-> WidgetNode s e
-> WidgetNode s e
-> WidgetResult s e,
Widget s e -> WidgetEnv s e -> WidgetNode s e -> WidgetResult s e
widgetDispose
:: WidgetEnv s e
-> WidgetNode s e
-> WidgetResult s e,
Widget s e -> WidgetEnv s e -> WidgetNode s e -> Maybe WidgetState
widgetGetState
:: WidgetEnv s e
-> WidgetNode s e
-> Maybe WidgetState,
Widget s e -> WidgetEnv s e -> WidgetNode s e -> WidgetInstanceNode
widgetGetInstanceTree
:: WidgetEnv s e
-> WidgetNode s e
-> WidgetInstanceNode,
Widget s e
-> WidgetEnv s e
-> WidgetNode s e
-> FocusDirection
-> Path
-> Maybe WidgetNodeInfo
widgetFindNextFocus
:: WidgetEnv s e
-> WidgetNode s e
-> FocusDirection
-> Path
-> Maybe WidgetNodeInfo,
Widget s e
-> WidgetEnv s e
-> WidgetNode s e
-> Path
-> Point
-> Maybe WidgetNodeInfo
widgetFindByPoint
:: WidgetEnv s e
-> WidgetNode s e
-> Path
-> Point
-> Maybe WidgetNodeInfo,
Widget s e
-> WidgetEnv s e -> WidgetNode s e -> Path -> Seq WidgetNodeInfo
widgetFindBranchByPath
:: WidgetEnv s e
-> WidgetNode s e
-> Path
-> Seq WidgetNodeInfo,
Widget s e
-> WidgetEnv s e
-> WidgetNode s e
-> Path
-> SystemEvent
-> Maybe (WidgetResult s e)
widgetHandleEvent
:: WidgetEnv s e
-> WidgetNode s e
-> Path
-> SystemEvent
-> Maybe (WidgetResult s e),
Widget s e
-> forall i.
Typeable i =>
WidgetEnv s e
-> WidgetNode s e -> Path -> i -> Maybe (WidgetResult s e)
widgetHandleMessage
:: forall i . Typeable i
=> WidgetEnv s e
-> WidgetNode s e
-> Path
-> i
-> Maybe (WidgetResult s e),
Widget s e -> WidgetEnv s e -> WidgetNode s e -> (SizeReq, SizeReq)
widgetGetSizeReq
:: WidgetEnv s e
-> WidgetNode s e
-> (SizeReq, SizeReq),
Widget s e
-> WidgetEnv s e
-> WidgetNode s e
-> Rect
-> (Path -> Bool)
-> WidgetResult s e
widgetResize
:: WidgetEnv s e
-> WidgetNode s e
-> Rect
-> (Path -> Bool)
-> WidgetResult s e,
Widget s e -> WidgetEnv s e -> WidgetNode s e -> Renderer -> IO ()
widgetRender
:: WidgetEnv s e
-> WidgetNode s e
-> Renderer
-> IO ()
}
instance Show (WidgetRequest s e) where
show :: WidgetRequest s e -> String
show WidgetRequest s e
IgnoreParentEvents = String
"IgnoreParentEvents"
show WidgetRequest s e
IgnoreChildrenEvents = String
"IgnoreChildrenEvents"
show (ResizeWidgets WidgetId
wid) = String
"ResizeWidgets: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show (ResizeWidgetsImmediate WidgetId
wid) = String
"ResizeWidgetsImmediate: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show (MoveFocus Maybe WidgetId
start FocusDirection
dir) = String
"MoveFocus: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Maybe WidgetId, FocusDirection) -> String
forall a. Show a => a -> String
show (Maybe WidgetId
start, FocusDirection
dir)
show (SetFocus WidgetId
path) = String
"SetFocus: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
path
show (GetClipboard WidgetId
wid) = String
"GetClipboard: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show (SetClipboard ClipboardData
_) = String
"SetClipboard"
show (StartTextInput Rect
rect) = String
"StartTextInput: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Rect -> String
forall a. Show a => a -> String
show Rect
rect
show WidgetRequest s e
StopTextInput = String
"StopTextInput"
show (SetOverlay WidgetId
wid Path
path) = String
"SetOverlay: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (WidgetId, Path) -> String
forall a. Show a => a -> String
show (WidgetId
wid, Path
path)
show (ResetOverlay WidgetId
wid) = String
"ResetOverlay: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show (SetCursorIcon WidgetId
wid CursorIcon
icon) = String
"SetCursorIcon: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (WidgetId, CursorIcon) -> String
forall a. Show a => a -> String
show (WidgetId
wid, CursorIcon
icon)
show (ResetCursorIcon WidgetId
wid) = String
"ResetCursorIcon: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show (StartDrag WidgetId
wid Path
path WidgetDragMsg
info) = String
"StartDrag: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (WidgetId, Path, WidgetDragMsg) -> String
forall a. Show a => a -> String
show (WidgetId
wid, Path
path, WidgetDragMsg
info)
show (StopDrag WidgetId
wid) = String
"StopDrag: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show WidgetRequest s e
RenderOnce = String
"RenderOnce"
show (RenderEvery WidgetId
wid Int
ms Maybe Int
repeat) = String
"RenderEvery: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (WidgetId, Int, Maybe Int) -> String
forall a. Show a => a -> String
show (WidgetId
wid, Int
ms, Maybe Int
repeat)
show (RenderStop WidgetId
wid) = String
"RenderStop: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show (RemoveRendererImage Text
name) = String
"RemoveRendererImage: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show Text
name
show ExitApplication{} = String
"ExitApplication"
show (UpdateWindow WindowRequest
req) = String
"UpdateWindow: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WindowRequest -> String
forall a. Show a => a -> String
show WindowRequest
req
show UpdateModel{} = String
"UpdateModel"
show (SetWidgetPath WidgetId
wid Path
path) = String
"SetWidgetPath: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ (WidgetId, Path) -> String
forall a. Show a => a -> String
show (WidgetId
wid, Path
path)
show (ResetWidgetPath WidgetId
wid) = String
"ResetWidgetPath: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetId -> String
forall a. Show a => a -> String
show WidgetId
wid
show RaiseEvent{} = String
"RaiseEvent"
show SendMessage{} = String
"SendMessage"
show RunTask{} = String
"RunTask"
show RunProducer{} = String
"RunProducer"
instance Show (WidgetResult s e) where
show :: WidgetResult s e -> String
show WidgetResult s e
result = String
"WidgetResult "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"{ _wrRequests: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Seq (WidgetRequest s e) -> String
forall a. Show a => a -> String
show (WidgetResult s e -> Seq (WidgetRequest s e)
forall s e. WidgetResult s e -> Seq (WidgetRequest s e)
_wrRequests WidgetResult s e
result)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", _wrNode: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetNode s e -> String
forall a. Show a => a -> String
show (WidgetResult s e -> WidgetNode s e
forall s e. WidgetResult s e -> WidgetNode s e
_wrNode WidgetResult s e
result)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" }"
instance Show (WidgetEnv s e) where
show :: WidgetEnv s e -> String
show WidgetEnv s e
wenv = String
"WidgetEnv "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"{ _weOs: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
forall a. Show a => a -> String
show (WidgetEnv s e -> Text
forall s e. WidgetEnv s e -> Text
_weOs WidgetEnv s e
wenv)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", _weWindowSize: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Size -> String
forall a. Show a => a -> String
show (WidgetEnv s e -> Size
forall s e. WidgetEnv s e -> Size
_weWindowSize WidgetEnv s e
wenv)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", _weFocusedPath: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Path -> String
forall a. Show a => a -> String
show (WidgetEnv s e -> Path
forall s e. WidgetEnv s e -> Path
_weFocusedPath WidgetEnv s e
wenv)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", _weTimestamp: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (WidgetEnv s e -> Int
forall s e. WidgetEnv s e -> Int
_weTimestamp WidgetEnv s e
wenv)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" }"
instance Show (WidgetNode s e) where
show :: WidgetNode s e -> String
show WidgetNode s e
node = String
"WidgetNode "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"{ _wnInfo: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ WidgetNodeInfo -> String
forall a. Show a => a -> String
show (WidgetNode s e -> WidgetNodeInfo
forall s e. WidgetNode s e -> WidgetNodeInfo
_wnInfo WidgetNode s e
node)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
", _wnChildren: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Seq (WidgetNode s e) -> String
forall a. Show a => a -> String
show (WidgetNode s e -> Seq (WidgetNode s e)
forall s e. WidgetNode s e -> Seq (WidgetNode s e)
_wnChildren WidgetNode s e
node)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" }"