monomer-1.1.1.0: A GUI library for writing native Haskell applications.
Copyright(c) 2018 Francisco Vallarino
LicenseBSD-3-Clause (see the LICENSE file)
Maintainerfjvallarino@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Monomer.Main.Types

Description

Basic types for Main module.

Synopsis

Documentation

type MonomerM s e m = (Eq s, MonadState (MonomerCtx s e) m, MonadCatch m, MonadIO m) Source #

Main Monomer monad.

data RenderMsg s e Source #

Messages received by the rendering thread.

Constructors

MsgRender (WidgetEnv s e) (WidgetNode s e) 
MsgResize Size 
MsgRemoveImage Text 
forall i. MsgRunInRender (TChan i) (IO i) 

Instances

Instances details
HasRenderChannel (MonomerCtx s e) (TChan (RenderMsg s e)) Source # 
Instance details

Defined in Monomer.Main.Lens

data RenderSchedule Source #

Requirements for periodic rendering by a widget. Start time is stored to calculate next frame based on the step ms. A maximum number of repetitions may be provided.

Instances

Instances details
Eq RenderSchedule Source # 
Instance details

Defined in Monomer.Main.Types

Show RenderSchedule Source # 
Instance details

Defined in Monomer.Main.Types

Generic RenderSchedule Source # 
Instance details

Defined in Monomer.Main.Types

Associated Types

type Rep RenderSchedule :: Type -> Type #

HasWidgetId RenderSchedule WidgetId Source # 
Instance details

Defined in Monomer.Main.Lens

HasStart RenderSchedule Int Source # 
Instance details

Defined in Monomer.Main.Lens

HasMs RenderSchedule Int Source # 
Instance details

Defined in Monomer.Main.Lens

HasRepeat RenderSchedule (Maybe Int) Source # 
Instance details

Defined in Monomer.Main.Lens

HasRenderSchedule (MonomerCtx s e) (Map WidgetId RenderSchedule) Source # 
Instance details

Defined in Monomer.Main.Lens

type Rep RenderSchedule Source # 
Instance details

Defined in Monomer.Main.Types

type Rep RenderSchedule = D1 ('MetaData "RenderSchedule" "Monomer.Main.Types" "monomer-1.1.1.0-2fSKkyoN5tiK63mqYpCfde" 'False) (C1 ('MetaCons "RenderSchedule" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_rsWidgetId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WidgetId) :*: S1 ('MetaSel ('Just "_rsStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "_rsMs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "_rsRepeat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Int)))))

data DragAction Source #

Drag action started by WidgetId, with an associated message.

data WidgetTask Source #

Asychronous widget task. Results must be provided as user defined, Typeable, types. Error handling should be done inside the task and reporting handled as part of the user type.

Constructors

forall i.Typeable i => WidgetTask WidgetId (Async i)

Task generating a single result (for example, an HTTP request).

forall i.Typeable i => WidgetProducer WidgetId (TChan i) (Async ())

Task generating a multiple result (for example, a Socket).

Instances

Instances details
HasWidgetTasks (MonomerCtx s e) (Seq WidgetTask) Source # 
Instance details

Defined in Monomer.Main.Lens

data MonomerCtx s e Source #

Current state of the Monomer runtime.

Constructors

MonomerCtx 

Fields

Instances

Instances details
HasWindowSize (MonomerCtx s e) Size Source # 
Instance details

Defined in Monomer.Main.Lens

HasInputStatus (MonomerCtx s e) InputStatus Source # 
Instance details

Defined in Monomer.Main.Lens

HasDpr (MonomerCtx s e) Double Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

dpr :: Lens' (MonomerCtx s e) Double Source #

HasWindow (MonomerCtx s e) Window Source # 
Instance details

Defined in Monomer.Main.Lens

HasRenderRequested (MonomerCtx s e) Bool Source # 
Instance details

Defined in Monomer.Main.Lens

HasMainModel (MonomerCtx s e) s Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

mainModel :: Lens' (MonomerCtx s e) s Source #

HasLeaveEnterPair (MonomerCtx s e) Bool Source # 
Instance details

Defined in Monomer.Main.Lens

HasFocusedWidgetId (MonomerCtx s e) WidgetId Source # 
Instance details

Defined in Monomer.Main.Lens

HasExitApplication (MonomerCtx s e) Bool Source # 
Instance details

Defined in Monomer.Main.Lens

HasEpr (MonomerCtx s e) Double Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

epr :: Lens' (MonomerCtx s e) Double Source #

HasMainBtnPress (MonomerCtx s e) (Maybe (Path, Point)) Source # 
Instance details

Defined in Monomer.Main.Lens

HasWidgetTasks (MonomerCtx s e) (Seq WidgetTask) Source # 
Instance details

Defined in Monomer.Main.Lens

HasResizeRequests (MonomerCtx s e) (Seq WidgetId) Source # 
Instance details

Defined in Monomer.Main.Lens

HasRenderChannel (MonomerCtx s e) (TChan (RenderMsg s e)) Source # 
Instance details

Defined in Monomer.Main.Lens

HasOverlayWidgetId (MonomerCtx s e) (Maybe WidgetId) Source # 
Instance details

Defined in Monomer.Main.Lens

HasHoveredWidgetId (MonomerCtx s e) (Maybe WidgetId) Source # 
Instance details

Defined in Monomer.Main.Lens

HasDragAction (MonomerCtx s e) (Maybe DragAction) Source # 
Instance details

Defined in Monomer.Main.Lens

HasCursorStack (MonomerCtx s e) [(WidgetId, CursorIcon)] Source # 
Instance details

Defined in Monomer.Main.Lens

HasWidgetPaths (MonomerCtx s e) (Map WidgetId Path) Source # 
Instance details

Defined in Monomer.Main.Lens

HasRenderSchedule (MonomerCtx s e) (Map WidgetId RenderSchedule) Source # 
Instance details

Defined in Monomer.Main.Lens

HasCursorIcons (MonomerCtx s e) (Map CursorIcon Cursor) Source # 
Instance details

Defined in Monomer.Main.Lens

data MainWindowState Source #

Requests for main window size.

Constructors

MainWindowNormal (Int, Int)

Normal window with a given size.

MainWindowMaximized

Maximized window.

MainWindowFullScreen

Full screen window.

data AppConfig e Source #

Main application config.

Constructors

AppConfig 

Fields

Instances

Instances details
Semigroup (AppConfig e) Source # 
Instance details

Defined in Monomer.Main.Types

Methods

(<>) :: AppConfig e -> AppConfig e -> AppConfig e #

sconcat :: NonEmpty (AppConfig e) -> AppConfig e #

stimes :: Integral b => b -> AppConfig e -> AppConfig e #

Monoid (AppConfig e) Source # 
Instance details

Defined in Monomer.Main.Types

Default (AppConfig e) Source # 
Instance details

Defined in Monomer.Main.Types

Methods

def :: AppConfig e #

HasTheme (AppConfig e) (Maybe Theme) Source # 
Instance details

Defined in Monomer.Main.Lens

HasMainButton (AppConfig e) (Maybe Button) Source # 
Instance details

Defined in Monomer.Main.Lens

HasContextButton (AppConfig e) (Maybe Button) Source # 
Instance details

Defined in Monomer.Main.Lens

HasWindowTitle (AppConfig e) (Maybe Text) Source # 
Instance details

Defined in Monomer.Main.Lens

HasWindowState (AppConfig e) (Maybe MainWindowState) Source # 
Instance details

Defined in Monomer.Main.Lens

HasWindowResizable (AppConfig e) (Maybe Bool) Source # 
Instance details

Defined in Monomer.Main.Lens

HasWindowBorder (AppConfig e) (Maybe Bool) Source # 
Instance details

Defined in Monomer.Main.Lens

HasUseRenderThread (AppConfig e) (Maybe Bool) Source # 
Instance details

Defined in Monomer.Main.Lens

HasScaleFactor (AppConfig e) (Maybe Double) Source # 
Instance details

Defined in Monomer.Main.Lens

HasResizeEvent (AppConfig e) [Rect -> e] Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

resizeEvent :: Lens' (AppConfig e) [Rect -> e] Source #

HasMaxFps (AppConfig e) (Maybe Int) Source # 
Instance details

Defined in Monomer.Main.Lens

HasInvertWheelY (AppConfig e) (Maybe Bool) Source # 
Instance details

Defined in Monomer.Main.Lens

HasInvertWheelX (AppConfig e) (Maybe Bool) Source # 
Instance details

Defined in Monomer.Main.Lens

HasInitEvent (AppConfig e) [e] Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

initEvent :: Lens' (AppConfig e) [e] Source #

HasFonts (AppConfig e) [FontDef] Source # 
Instance details

Defined in Monomer.Main.Lens

HasExitEvent (AppConfig e) [e] Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

exitEvent :: Lens' (AppConfig e) [e] Source #

HasDisposeEvent (AppConfig e) [e] Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

disposeEvent :: Lens' (AppConfig e) [e] Source #

appWindowState :: MainWindowState -> AppConfig e Source #

Initial size of the main window.

appWindowTitle :: Text -> AppConfig e Source #

Title of the main window.

appWindowResizable :: Bool -> AppConfig e Source #

Whether the main window is resizable.

appWindowBorder :: Bool -> AppConfig e Source #

Whether the main window has a border.

appRenderOnMainThread :: AppConfig e Source #

Performs rendering on the main thread. On macOS and Windows this also disables continuous rendering on window resize, but in some Linux configurations it still works.

This option is useful when OpenGL driver issues prevent normal startup showing the "Unable to make GL context current" error.

It can also be used for single threaded applications (without -threaded).

appMaxFps :: Int -> AppConfig e Source #

Max number of FPS the application will run on. It does not necessarily mean rendering will happen every frame, but events and schedules will be checked at this rate and may cause it.

appScaleFactor :: Double -> AppConfig e Source #

Scale factor to apply. This factor only affects the content, not the size of the window. It is applied in addition to the OS zoom in plaforms where it is reliably detected (i.e., system scaling may not be detected reliably on Linux).

appFontDef :: Text -> Text -> AppConfig e Source #

Available fonts to the application. An empty list will make it impossible to render text.

appTheme :: Theme -> AppConfig e Source #

Initial theme.

appInitEvent :: e -> AppConfig e Source #

Initial event, useful for loading resources.

appDisposeEvent :: e -> AppConfig e Source #

Dispose event, useful for closing resources.

appExitEvent :: e -> AppConfig e Source #

Exit event, useful for cancelling an application close event.

appResizeEvent :: (Rect -> e) -> AppConfig e Source #

Resize event handler.

appMainButton :: Button -> AppConfig e Source #

Defines which mouse button is considered main.

appContextButton :: Button -> AppConfig e Source #

Defines which mouse button is considered secondary or context button.

appInvertWheelX :: Bool -> AppConfig e Source #

Whether the horizontal wheel/trackpad movement should be inverted. In general platform detection should do the right thing.

appInvertWheelY :: Bool -> AppConfig e Source #

Whether the vertical wheel/trackpad movement should be inverted. In general platform detection should do the right thing.