monomer-1.5.0.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 HaskellSafe-Inferred
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

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

Instances

Instances details
HasRenderMethod (MonomerCtx s e) (Either Renderer (TChan (RenderMsg s e))) Source # 
Instance details

Defined in Monomer.Main.Lens

data RenderSetupResult Source #

Result from attempting to set up the secondary rendering thread.

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
Generic RenderSchedule Source # 
Instance details

Defined in Monomer.Main.Types

Associated Types

type Rep RenderSchedule :: Type -> Type #

Show RenderSchedule Source # 
Instance details

Defined in Monomer.Main.Types

Eq RenderSchedule Source # 
Instance details

Defined in Monomer.Main.Types

HasWidgetId RenderSchedule WidgetId Source # 
Instance details

Defined in Monomer.Main.Lens

HasMs RenderSchedule Millisecond Source # 
Instance details

Defined in Monomer.Main.Lens

HasStart RenderSchedule Millisecond 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.5.0.0-Qyhewrg5o52dfUHeNdP9B" 'False) (C1 ('MetaCons "RenderSchedule" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_rsWidgetId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WidgetId) :*: S1 ('MetaSel ('Just "_rsStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Millisecond)) :*: (S1 ('MetaSel ('Just "_rsMs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Millisecond) :*: 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
HasDpr (MonomerCtx s e) Double Source # 
Instance details

Defined in Monomer.Main.Lens

Methods

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

HasInputStatus (MonomerCtx s e) InputStatus Source # 
Instance details

Defined in Monomer.Main.Lens

HasWindowSize (MonomerCtx s e) Size 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 #

HasExitApplication (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

HasLeaveEnterPair (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 #

HasRenderRequested (MonomerCtx s e) Bool Source # 
Instance details

Defined in Monomer.Main.Lens

HasWindow (MonomerCtx s e) Window Source # 
Instance details

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

HasRenderMethod (MonomerCtx s e) (Either Renderer (TChan (RenderMsg s e))) Source # 
Instance details

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

HasWidgetPaths (MonomerCtx s e) (Map WidgetId Path) 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
Monoid (AppConfig e) Source # 
Instance details

Defined in Monomer.Main.Types

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 #

Default (AppConfig e) Source # 
Instance details

Defined in Monomer.Main.Types

Methods

def :: AppConfig e #

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

Methods

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

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

Defined in Monomer.Main.Lens

Methods

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

HasFonts (AppConfig e) [FontDef] 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 #

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

HasMaxFps (AppConfig e) (Maybe Int) 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 #

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

Defined in Monomer.Main.Lens

HasUseRenderThread (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

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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

Defined in Monomer.Main.Lens

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.

appWindowIcon :: Text -> AppConfig e Source #

Path to an icon file in BMP format.

appRenderOnMainThread :: AppConfig e Source #

Deprecated: Should no longer be needed. Check appRenderOnMainThread's Haddock page.

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 configuration option was originally available to handle:

  • OpenGL driver issues which prevented normal startup showing the "Unable to make GL context current" error.
  • Single threaded applications (without -threaded) which cannot use forkOS.

This flag is no longer necessary for those cases, since the library will:

  • Attempt to fall back to rendering on the main thread if setting up a secondary rendering thread fails.
  • Will not attempt to set up a secondary rendering thread if the runtime does not support bound threads (i.e. compiled without the -threaded flag).

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 to the viewport. This factor only affects the content, not the size of the window. It is applied in addition to the detected display scale factor, and can be useful if the detected value is not the desired.

appDisableAutoScale :: Bool -> AppConfig e Source #

Whether display scaling detection should not be attempted. If set to True, the display scale will be set to 1. This flag does not cause an effect on macOS.

Disabling auto scaling also affects window size on Linux and Windows in the cases where the library would have applied scaling. This happens because window and viewport size are the same in those operating systems. Window size can be adjusted with appWindowState.

The logic for detecting display scaling varies depending on the platform:

macOS

Scaling can be detected based on the window size and viewport size; the ratio between these two give the scaling factor.

Using window and viewport size for detecting DPI only works on macOS; both Windows and Linux return the same value for window and viewport size.

Windows

SDL_GetDisplayDPI returns the DPI of the screen, and dividing by 96 gives the scaling factor. This factor is used to scale the window size and the content.

Linux

The situation is more complex, since SDL_GetDisplayDPI does not always return valid information. There is not a practical DPI/scale detection solution that works for all combinations of Linux display servers and window managers. Even when using the most popular window managers, the scaling factor may be handled differently by the distribution (GNOME in Ubuntu). For a reference of some of the existing options for DPI scaling detection, check here: https:/wiki.archlinux.orgtitle/HiDPI.

Considering the above, when SDL_GetDisplayDPI fails, the library assumes that a screen width larger than 1920 belongs to an HiDPI display and uses a scale factor of 2. This factor is used to scale the window size and the content.

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

Available fonts to the application, loaded from the specified path. Specifying no fonts will make it impossible to render text.

appFontDefMem :: Text -> ByteString -> AppConfig e Source #

Available fonts to the application, loaded from the bytes in memory. Specifying no fonts will make it impossible to render text.

One use case for this function is to embed fonts in the application, without the need to distribute the font files. The file-embed library can be used for this. appFontDefMemory "memoryFont" $(embedFile "dirName/fileName")

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.

appDisableCompositing :: Bool -> AppConfig e Source #

Whether compositing should be disabled. Linux only, ignored in other platforms. Defaults to False.

Desktop applications should leave compositing as is since disabling it may cause visual glitches in other programs. When creating games or fullscreen applications, disabling compositing may improve performance.

appDisableScreensaver :: Bool -> AppConfig e Source #

Whether the screensaver should be disabled. Defaults to False.

Desktop applications should leave the screensaver as is since disabling it also affects power saving features, including turning off the screen. When creating games or fullscreen applications, disabling the screensaver may make sense.