monomer-1.4.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.Common.BasicTypes

Description

Basic types used across the library.

Synopsis

Documentation

type PathStep = Int Source #

An index in the list of children of a widget.

type Path = Seq PathStep Source #

A sequence of steps, usually from the root.

type Factor = Double Source #

Resize factor.

data Point Source #

Point in the 2D space.

Constructors

Point 

Fields

Instances

Instances details
Eq Point Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

(==) :: Point -> Point -> Bool #

(/=) :: Point -> Point -> Bool #

Show Point Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Generic Point Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Associated Types

type Rep Point :: Type -> Type #

Methods

from :: Point -> Rep Point x #

to :: Rep Point x -> Point #

Default Point Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

def :: Point #

HasY Point Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasX Point Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasMousePosPrev InputStatus Point Source # 
Instance details

Defined in Monomer.Event.Lens

HasMousePos InputStatus Point Source # 
Instance details

Defined in Monomer.Event.Lens

HasOffset (WidgetEnv s e) Point Source # 
Instance details

Defined in Monomer.Core.Lens

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

Defined in Monomer.Core.Lens

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

Defined in Monomer.Main.Lens

HasInTopLayer (WidgetEnv s e) (Point -> Bool) Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

inTopLayer :: Lens' (WidgetEnv s e) (Point -> Bool) Source #

type Rep Point Source # 
Instance details

Defined in Monomer.Common.BasicTypes

type Rep Point = D1 ('MetaData "Point" "Monomer.Common.BasicTypes" "monomer-1.4.0.0-inplace" 'False) (C1 ('MetaCons "Point" 'PrefixI 'True) (S1 ('MetaSel ('Just "_pX") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "_pY") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double)))

data Size Source #

Width and height, used for size requirements.

Constructors

Size 

Fields

Instances

Instances details
Eq Size Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Show Size Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Generic Size Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Associated Types

type Rep Size :: Type -> Type #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

Default Size Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

def :: Size #

HasW Size Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasH Size Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasSize ImageDef Size Source # 
Instance details

Defined in Monomer.Graphics.Lens

HasSize TextLine Size Source # 
Instance details

Defined in Monomer.Graphics.Lens

HasWindowSize (WidgetEnv s e) Size Source # 
Instance details

Defined in Monomer.Core.Lens

HasWindowSize (MonomerCtx s e) Size Source # 
Instance details

Defined in Monomer.Main.Lens

type Rep Size Source # 
Instance details

Defined in Monomer.Common.BasicTypes

type Rep Size = D1 ('MetaData "Size" "Monomer.Common.BasicTypes" "monomer-1.4.0.0-inplace" 'False) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "_sW") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "_sH") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double)))

data Rect Source #

Rectangle, usually representing an area of the screen.

Constructors

Rect 

Fields

Instances

Instances details
Eq Rect Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

(==) :: Rect -> Rect -> Bool #

(/=) :: Rect -> Rect -> Bool #

Show Rect Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

showsPrec :: Int -> Rect -> ShowS #

show :: Rect -> String #

showList :: [Rect] -> ShowS #

Generic Rect Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Associated Types

type Rep Rect :: Type -> Type #

Methods

from :: Rect -> Rep Rect x #

to :: Rep Rect x -> Rect #

Default Rect Source # 
Instance details

Defined in Monomer.Common.BasicTypes

Methods

def :: Rect #

HasY Rect Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasX Rect Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasW Rect Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasH Rect Double Source # 
Instance details

Defined in Monomer.Common.Lens

HasViewport WidgetNodeInfo Rect Source # 
Instance details

Defined in Monomer.Core.Lens

HasRect TextLine Rect Source # 
Instance details

Defined in Monomer.Graphics.Lens

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

Defined in Monomer.Main.Lens

Methods

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

HasViewport (WidgetEnv s e) Rect Source # 
Instance details

Defined in Monomer.Core.Lens

CmbOnResize (CompositeCfg s e sp ep) e Rect Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onResize :: (Rect -> e) -> CompositeCfg s e sp ep Source #

type Rep Rect Source # 
Instance details

Defined in Monomer.Common.BasicTypes

type Rep Rect = D1 ('MetaData "Rect" "Monomer.Common.BasicTypes" "monomer-1.4.0.0-inplace" 'False) (C1 ('MetaCons "Rect" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_rX") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "_rY") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double)) :*: (S1 ('MetaSel ('Just "_rW") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double) :*: S1 ('MetaSel ('Just "_rH") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Double))))

emptyPath :: Path Source #

An empty path.

rootPath :: Path Source #

The path of the root element.

pointInRect :: Point -> Rect -> Bool Source #

Checks if a point is inside the given rect.

pointInEllipse :: Point -> Rect -> Bool Source #

Checks if a point is inside the given ellipse.

addPoint :: Point -> Point -> Point Source #

Adds two points.

subPoint :: Point -> Point -> Point Source #

Subtracts one point from another.

mulPoint :: Double -> Point -> Point Source #

Multiplies the coordinates of a point by the given factor.

midPoint :: Point -> Point -> Point Source #

Returns the middle between two points.

interpolatePoints :: Point -> Point -> Double -> Point Source #

Returns the point between a and b, f units away from a.

negPoint :: Point -> Point Source #

Negates the coordinates of a point.

coordInRectH :: Double -> Rect -> Bool Source #

Checks if a coordinate is inside the horizontal range of a rect.

coordInRectY :: Double -> Rect -> Bool Source #

Checks if a coordinate is inside the vertical range of a rect.

addToSize :: Size -> Double -> Double -> Maybe Size Source #

Adds width and height to a Size.

subtractFromSize :: Size -> Double -> Double -> Maybe Size Source #

Subtracts width and height from a Size.

moveRect :: Point -> Rect -> Rect Source #

Moves a rect by the provided offset.

mulRect :: Double -> Rect -> Rect Source #

Scales a rect by the provided factor.

rectCenter :: Rect -> Point Source #

Returns the middle point of a rect.

rectInRect :: Rect -> Rect -> Bool Source #

Checks if a rectangle is completely inside a rect.

rectInRectH :: Rect -> Rect -> Bool Source #

Checks if a rectangle is completely inside a rectangle horizontal area.

rectInRectV :: Rect -> Rect -> Bool Source #

Checks if a rectangle is completely inside a rectangle vertical area.

rectsOverlap :: Rect -> Rect -> Bool Source #

Checks if a rectangle overlaps another rectangle.

rectBoundedPoint :: Rect -> Point -> Point Source #

Returns a point bounded to the horizontal and vertical limits of a rect.

rectFromPoints :: Point -> Point -> Rect Source #

Returns a rect using the provided points as boundaries

addToRect :: Rect -> Double -> Double -> Double -> Double -> Maybe Rect Source #

Adds individual x, y, w and h coordinates to a rect.

subtractFromRect :: Rect -> Double -> Double -> Double -> Double -> Maybe Rect Source #

Subtracts individual x, y, w and h coordinates from a rect.

intersectRects :: Rect -> Rect -> Maybe Rect Source #

Returns the intersection of two rects, if any.