tinytools-0.1.0.3
Safe HaskellSafe-Inferred
LanguageHaskell2010

Potato.Flow.Math

Synopsis

Documentation

type XY = V2 Int Source #

data LBox Source #

a point in screen space should only be used by VC, so does not belong here newtype VPoint = VPoint (Int, Int) deriving (Generic, Show, FromJSON, ToJSON)

a box in logical space note size is non inclusive e.g. an LBox with size (1,1) is exactly 1 point at ul e.g. an LBox with size (0,0) contains nothing

Constructors

LBox 

Fields

Instances

Instances details
FromJSON LBox Source # 
Instance details

Defined in Potato.Flow.Math

ToJSON LBox Source # 
Instance details

Defined in Potato.Flow.Math

Generic LBox Source # 
Instance details

Defined in Potato.Flow.Math

Associated Types

type Rep LBox :: Type -> Type #

Methods

from :: LBox -> Rep LBox x #

to :: Rep LBox x -> LBox #

Show LBox Source # 
Instance details

Defined in Potato.Flow.Math

Methods

showsPrec :: Int -> LBox -> ShowS #

show :: LBox -> String #

showList :: [LBox] -> ShowS #

Binary LBox Source # 
Instance details

Defined in Potato.Flow.Math

Methods

put :: LBox -> Put #

get :: Get LBox #

putList :: [LBox] -> Put #

NFData LBox Source # 
Instance details

Defined in Potato.Flow.Math

Methods

rnf :: LBox -> () #

Eq LBox Source # 
Instance details

Defined in Potato.Flow.Math

Methods

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

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

TransformMe LBox Source # 
Instance details

Defined in Potato.Flow.Methods.LineTypes

Delta LBox DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

type Rep LBox Source # 
Instance details

Defined in Potato.Flow.Math

type Rep LBox = D1 ('MetaData "LBox" "Potato.Flow.Math" "tinytools-0.1.0.3-HF5s50ZrT30LQps3nQySnP" 'False) (C1 ('MetaCons "LBox" 'PrefixI 'True) (S1 ('MetaSel ('Just "_lBox_tl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY) :*: S1 ('MetaSel ('Just "_lBox_size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY)))

make_0area_lBox_from_XY :: XY -> LBox Source #

returns a 0 area LBox

make_1area_lBox_from_XY :: XY -> LBox Source #

returns a 1 area LBox

make_lBox_from_XYs :: XY -> XY -> LBox Source #

always returns a canonical LBox

make_lBox_from_XYlist :: [XY] -> LBox Source #

always returns a canonical LBox

lBox_to_axis :: LBox -> (Int, Int, Int, Int) Source #

(left, right, top, bottom) right and bottom are non-inclusive

add_XY_to_lBox :: XY -> LBox -> LBox Source #

always returns a canonical LBox bottom/right XYs cells are not included in

make_lBox_from_axis :: (Int, Int, Int, Int) -> LBox Source #

right and bottom axis are non-inclusive

union_lBox :: LBox -> LBox -> LBox Source #

inverted LBox are treated as if not inverted

intersect_lBox :: LBox -> LBox -> Maybe LBox Source #

inverted LBox are treated as if not inverted

substract_lBox :: LBox -> LBox -> [LBox] Source #

substract lb2 from lb1 and return [LBox] representing the difference

data CanonicalLBox Source #

CanonicalLBox is always has non-negative width/height and tracks which axis are flipped to return back to original LBox first Bool is if x values are flipped, second is for y

Constructors

CanonicalLBox Bool Bool LBox 

canonicalLBox_from_lBox_ :: LBox -> LBox Source #

same as canonicalLBox_from_lBox but returns just the canonical LBox

class Delta x dx where Source #

Methods

plusDelta :: x -> dx -> x Source #

minusDelta :: x -> dx -> x Source #

Instances

Instances details
Delta LBox DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

Delta XY DeltaXY Source # 
Instance details

Defined in Potato.Flow.Math

Delta XY XY Source # 
Instance details

Defined in Potato.Flow.Math

Methods

plusDelta :: XY -> XY -> XY Source #

minusDelta :: XY -> XY -> XY Source #

Delta LineStyle DeltaLineStyle Source # 
Instance details

Defined in Potato.Flow.Types

Delta SAutoLine CLine Source # 
Instance details

Defined in Potato.Flow.Types

Delta SBox CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

Delta SBox CBoxType Source # 
Instance details

Defined in Potato.Flow.Types

Delta SBoxText CBoxText Source # 
Instance details

Defined in Potato.Flow.Types

Delta SElt DeltaTextAreaToggle Source # 
Instance details

Defined in Potato.Flow.Types

Delta SEltLabel CRename Source # 
Instance details

Defined in Potato.Flow.Types

Delta SuperStyle DeltaSuperStyle Source # 
Instance details

Defined in Potato.Flow.Types

Delta TextAlign DeltaTextAlign Source # 
Instance details

Defined in Potato.Flow.Types

Delta TextAreaMapping DeltaTextArea Source # 
Instance details

Defined in Potato.Flow.Types

Delta TextStyle DeltaTextStyle Source # 
Instance details

Defined in Potato.Flow.Types

(Show a, Eq a) => Delta a (a, a) Source # 
Instance details

Defined in Potato.Flow.Math

Methods

plusDelta :: a -> (a, a) -> a Source #

minusDelta :: a -> (a, a) -> a Source #

Delta (Maybe Text) DeltaMaybeText Source # 
Instance details

Defined in Potato.Flow.Types

(Delta a c, Delta b d) => Delta (a, b) (c, d) Source # 
Instance details

Defined in Potato.Flow.Math

Methods

plusDelta :: (a, b) -> (c, d) -> (a, b) Source #

minusDelta :: (a, b) -> (c, d) -> (a, b) Source #

newtype DeltaXY Source #

Constructors

DeltaXY XY 

Instances

Instances details
Generic DeltaXY Source # 
Instance details

Defined in Potato.Flow.Math

Associated Types

type Rep DeltaXY :: Type -> Type #

Methods

from :: DeltaXY -> Rep DeltaXY x #

to :: Rep DeltaXY x -> DeltaXY #

Show DeltaXY Source # 
Instance details

Defined in Potato.Flow.Math

NFData DeltaXY Source # 
Instance details

Defined in Potato.Flow.Math

Methods

rnf :: DeltaXY -> () #

Eq DeltaXY Source # 
Instance details

Defined in Potato.Flow.Math

Methods

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

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

Delta XY DeltaXY Source # 
Instance details

Defined in Potato.Flow.Math

type Rep DeltaXY Source # 
Instance details

Defined in Potato.Flow.Math

type Rep DeltaXY = D1 ('MetaData "DeltaXY" "Potato.Flow.Math" "tinytools-0.1.0.3-HF5s50ZrT30LQps3nQySnP" 'True) (C1 ('MetaCons "DeltaXY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY)))

data DeltaLBox Source #

Instances

Instances details
Generic DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

Associated Types

type Rep DeltaLBox :: Type -> Type #

Show DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

NFData DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

Methods

rnf :: DeltaLBox -> () #

Eq DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

Delta LBox DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

type Rep DeltaLBox Source # 
Instance details

Defined in Potato.Flow.Math

type Rep DeltaLBox = D1 ('MetaData "DeltaLBox" "Potato.Flow.Math" "tinytools-0.1.0.3-HF5s50ZrT30LQps3nQySnP" 'False) (C1 ('MetaCons "DeltaLBox" 'PrefixI 'True) (S1 ('MetaSel ('Just "_deltaLBox_translate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY) :*: S1 ('MetaSel ('Just "_deltaLBox_resizeBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 XY)))

module Linear.V2

Orphan instances