module Simple.UI.Layouts.FillLayout (
FillLayout (..),
FillLayoutData (..),
fillLayoutVerticalNew,
fillLayoutHorizontalNew,
def
) where
import Control.Monad
import Data.Default.Class
import Data.Maybe
import Simple.UI.Core.Attribute
import Simple.UI.Core.Draw
import Simple.UI.Core.Internal.UIApp
import Simple.UI.Core.ListenerList
import Simple.UI.Widgets.Container
import Simple.UI.Widgets.Widget
data FillLayout = FillLayoutHorizontal
| FillLayoutVertical
deriving (FillLayout -> FillLayout -> Bool
(FillLayout -> FillLayout -> Bool)
-> (FillLayout -> FillLayout -> Bool) -> Eq FillLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FillLayout -> FillLayout -> Bool
$c/= :: FillLayout -> FillLayout -> Bool
== :: FillLayout -> FillLayout -> Bool
$c== :: FillLayout -> FillLayout -> Bool
Eq)
data FillLayoutData = FillLayoutData
{ FillLayoutData -> Bool
fillLayoutHExpand :: Bool
, FillLayoutData -> Bool
fillLayoutVExpand :: Bool
}
instance LayoutClass FillLayout where
type LayoutData FillLayout = FillLayoutData
layoutDraw :: c FillLayout -> Drawing -> Int -> Int -> UIApp u ()
layoutDraw c FillLayout
container Drawing
drawing Int
width Int
height = do
FillLayout
_layout <- c FillLayout
-> (c FillLayout -> Attribute FillLayout)
-> ReaderT (AppConfig u) (StateT AppState IO) FillLayout
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get c FillLayout
container c FillLayout -> Attribute FillLayout
forall (w :: * -> *) a. ContainerClass w => w a -> Attribute a
layout
[(Widget, FillLayoutData)]
_widgets <- c FillLayout
-> (c FillLayout -> Attribute [(Widget, FillLayoutData)])
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get c FillLayout
container c FillLayout -> Attribute [(Widget, FillLayoutData)]
forall (w :: * -> *) a.
ContainerClass w =>
w a -> AttributeList (Widget, LayoutData a)
widgets
FillLayout
-> [(Widget, FillLayoutData)]
-> Drawing
-> Int
-> Int
-> UIApp u ()
forall u.
FillLayout
-> [(Widget, FillLayoutData)]
-> Drawing
-> Int
-> Int
-> UIApp u ()
fillLayoutDraw FillLayout
_layout [(Widget, FillLayoutData)]
_widgets Drawing
drawing Int
width Int
height
layoutComputeSize :: c FillLayout -> UIApp u (Int, Int)
layoutComputeSize c FillLayout
container = do
[(Widget, FillLayoutData)]
_widgets <- c FillLayout
-> (c FillLayout -> Attribute [(Widget, FillLayoutData)])
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get c FillLayout
container c FillLayout -> Attribute [(Widget, FillLayoutData)]
forall (w :: * -> *) a.
ContainerClass w =>
w a -> AttributeList (Widget, LayoutData a)
widgets
if [(Widget, FillLayoutData)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Widget, FillLayoutData)]
_widgets
then
(Int, Int) -> UIApp u (Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
0, Int
0)
else do
FillLayout
_layout <- c FillLayout
-> (c FillLayout -> Attribute FillLayout)
-> ReaderT (AppConfig u) (StateT AppState IO) FillLayout
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get c FillLayout
container c FillLayout -> Attribute FillLayout
forall (w :: * -> *) a. ContainerClass w => w a -> Attribute a
layout
[(Int, Int)]
sizes <- [(Widget, FillLayoutData)]
-> ((Widget, FillLayoutData) -> UIApp u (Int, Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [(Int, Int)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [(Widget, FillLayoutData)]
_widgets (((Widget, FillLayoutData) -> UIApp u (Int, Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [(Int, Int)])
-> ((Widget, FillLayoutData) -> UIApp u (Int, Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [(Int, Int)]
forall a b. (a -> b) -> a -> b
$ \(Widget
widget, FillLayoutData
_) -> do
Bool
v <- Widget
-> (Widget -> Attribute Bool)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get Widget
widget Widget -> Attribute Bool
forall w. WidgetClass w => w -> Attribute Bool
visible
if Bool
v then Widget -> UIApp u (Int, Int)
forall w u. WidgetClass w => w -> UIApp u (Int, Int)
computeSize Widget
widget else (Int, Int) -> UIApp u (Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
0, Int
0)
FillLayout -> [(Int, Int)] -> UIApp u (Int, Int)
forall u. FillLayout -> [(Int, Int)] -> UIApp u (Int, Int)
fillLayoutComputeSize FillLayout
_layout [(Int, Int)]
sizes
instance Default FillLayoutData where
def :: FillLayoutData
def = FillLayoutData :: Bool -> Bool -> FillLayoutData
FillLayoutData
{ fillLayoutHExpand :: Bool
fillLayoutHExpand = Bool
True
, fillLayoutVExpand :: Bool
fillLayoutVExpand = Bool
True
}
fillLayoutComputeSize :: FillLayout -> [(Int, Int)] -> UIApp u (Int, Int)
fillLayoutComputeSize :: FillLayout -> [(Int, Int)] -> UIApp u (Int, Int)
fillLayoutComputeSize FillLayout
FillLayoutVertical [(Int, Int)]
sizes =
(Int, Int) -> UIApp u (Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ ((Int, Int) -> Int) -> [(Int, Int)] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Int) -> Int
forall a b. (a, b) -> a
fst [(Int, Int)]
sizes, [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ ((Int, Int) -> Int) -> [(Int, Int)] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Int) -> Int
forall a b. (a, b) -> b
snd [(Int, Int)]
sizes)
fillLayoutComputeSize FillLayout
FillLayoutHorizontal [(Int, Int)]
sizes =
(Int, Int) -> UIApp u (Int, Int)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ ((Int, Int) -> Int) -> [(Int, Int)] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Int) -> Int
forall a b. (a, b) -> a
fst [(Int, Int)]
sizes, [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ ((Int, Int) -> Int) -> [(Int, Int)] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int, Int) -> Int
forall a b. (a, b) -> b
snd [(Int, Int)]
sizes)
fillLayoutDraw :: FillLayout -> [(Widget, FillLayoutData)] -> Drawing -> Int -> Int -> UIApp u ()
fillLayoutDraw :: FillLayout
-> [(Widget, FillLayoutData)]
-> Drawing
-> Int
-> Int
-> UIApp u ()
fillLayoutDraw FillLayout
FillLayoutVertical [(Widget, FillLayoutData)]
_widgets Drawing
drawing Int
width Int
height = do
[(Widget, FillLayoutData)]
filteredWidgets <- (((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> [(Widget, FillLayoutData)]
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)])
-> [(Widget, FillLayoutData)]
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> [(Widget, FillLayoutData)]
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM [(Widget, FillLayoutData)]
_widgets (((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)])
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall a b. (a -> b) -> a -> b
$ \(Widget
widget, FillLayoutData
_) ->
Widget
-> (Widget -> Attribute Bool)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get Widget
widget Widget -> Attribute Bool
forall w. WidgetClass w => w -> Attribute Bool
visible
[Maybe Int]
heights <- [(Widget, FillLayoutData)]
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [Maybe Int]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [(Widget, FillLayoutData)]
filteredWidgets (((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [Maybe Int])
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [Maybe Int]
forall a b. (a -> b) -> a -> b
$ \(Widget
widget, FillLayoutData
layoutData) ->
if FillLayoutData -> Bool
fillLayoutVExpand FillLayoutData
layoutData
then Maybe Int -> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
else Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int)
-> ((Int, Int) -> Int) -> (Int, Int) -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> Int
forall a b. (a, b) -> b
snd ((Int, Int) -> Maybe Int)
-> ReaderT (AppConfig u) (StateT AppState IO) (Int, Int)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Widget -> ReaderT (AppConfig u) (StateT AppState IO) (Int, Int)
forall w u. WidgetClass w => w -> UIApp u (Int, Int)
computeSize Widget
widget
let sumHeight :: Int
sumHeight = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ [Maybe Int] -> [Int]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Int]
heights
let deltaH :: Int
deltaH = if Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sumHeight Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then Int
0 else Int
height Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sumHeight
let countEW :: Int
countEW = [(Widget, FillLayoutData)] -> Int
forall (t :: * -> *) a a.
(Foldable t, Num a, Functor t) =>
t (a, FillLayoutData) -> a
countExpandedWidgets [(Widget, FillLayoutData)]
filteredWidgets
let expandedH :: Int
expandedH = if Int
countEW Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
0 else Int
deltaH Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
countEW
let restH :: Int
restH = if Int
countEW Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
deltaH else Int
deltaH Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
countEW
[Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets (((Widget, FillLayoutData) -> Widget)
-> [(Widget, FillLayoutData)] -> [Widget]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Widget, FillLayoutData) -> Widget
forall a b. (a, b) -> a
fst [(Widget, FillLayoutData)]
filteredWidgets) [Maybe Int]
heights Int
expandedH Int
restH Int
0
where
drawWidgets :: [Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets [] [Maybe Int]
_ Int
_ Int
_ Int
_ = () -> UIApp u ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
drawWidgets [Widget]
_ [] Int
_ Int
_ Int
_ = () -> UIApp u ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
drawWidgets (Widget
_widget:[Widget]
ws) (Maybe Int
maybeHeight:[Maybe Int]
mhs) Int
expandedH Int
restH Int
y =
case Maybe Int
maybeHeight of
Maybe Int
Nothing -> do
let h :: Int
h = Int
expandedH Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
nat Int
restH
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
forall u.
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
layoutDrawWidget Widget
_widget Drawing
drawing Int
0 Int
y Int
width Int
h
[Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets [Widget]
ws [Maybe Int]
mhs Int
expandedH (Int -> Int
dec Int
restH) (Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
h)
Just Int
wHeight -> do
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
forall u.
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
layoutDrawWidget Widget
_widget Drawing
drawing Int
0 Int
y Int
width Int
wHeight
[Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets [Widget]
ws [Maybe Int]
mhs Int
expandedH Int
restH (Int
y Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
wHeight)
countExpandedWidgets :: t (a, FillLayoutData) -> a
countExpandedWidgets t (a, FillLayoutData)
filteredWidgets = t a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (t a -> a) -> t a -> a
forall a b. (a -> b) -> a -> b
$
(((a, FillLayoutData) -> a) -> t (a, FillLayoutData) -> t a)
-> t (a, FillLayoutData) -> ((a, FillLayoutData) -> a) -> t a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((a, FillLayoutData) -> a) -> t (a, FillLayoutData) -> t a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t (a, FillLayoutData)
filteredWidgets (((a, FillLayoutData) -> a) -> t a)
-> ((a, FillLayoutData) -> a) -> t a
forall a b. (a -> b) -> a -> b
$ \(a
_, FillLayoutData
layoutData) ->
if FillLayoutData -> Bool
fillLayoutVExpand FillLayoutData
layoutData
then a
1
else a
0
fillLayoutDraw FillLayout
FillLayoutHorizontal [(Widget, FillLayoutData)]
_widgets Drawing
drawing Int
width Int
height = do
[(Widget, FillLayoutData)]
filteredWidgets <- (((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> [(Widget, FillLayoutData)]
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)])
-> [(Widget, FillLayoutData)]
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> [(Widget, FillLayoutData)]
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM [(Widget, FillLayoutData)]
_widgets (((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)])
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool)
-> ReaderT
(AppConfig u) (StateT AppState IO) [(Widget, FillLayoutData)]
forall a b. (a -> b) -> a -> b
$ \(Widget
widget, FillLayoutData
_) ->
Widget
-> (Widget -> Attribute Bool)
-> ReaderT (AppConfig u) (StateT AppState IO) Bool
forall (m :: * -> *) s a.
MonadIO m =>
s -> (s -> Attribute a) -> m a
get Widget
widget Widget -> Attribute Bool
forall w. WidgetClass w => w -> Attribute Bool
visible
[Maybe Int]
widths <- [(Widget, FillLayoutData)]
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [Maybe Int]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [(Widget, FillLayoutData)]
filteredWidgets (((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [Maybe Int])
-> ((Widget, FillLayoutData)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int))
-> ReaderT (AppConfig u) (StateT AppState IO) [Maybe Int]
forall a b. (a -> b) -> a -> b
$ \(Widget
widget, FillLayoutData
layoutData) ->
if FillLayoutData -> Bool
fillLayoutHExpand FillLayoutData
layoutData
then Maybe Int -> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
else Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int)
-> ((Int, Int) -> Int) -> (Int, Int) -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> Int
forall a b. (a, b) -> a
fst ((Int, Int) -> Maybe Int)
-> ReaderT (AppConfig u) (StateT AppState IO) (Int, Int)
-> ReaderT (AppConfig u) (StateT AppState IO) (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Widget -> ReaderT (AppConfig u) (StateT AppState IO) (Int, Int)
forall w u. WidgetClass w => w -> UIApp u (Int, Int)
computeSize Widget
widget
let sumWidth :: Int
sumWidth = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ [Maybe Int] -> [Int]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Int]
widths
let deltaW :: Int
deltaW = if Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sumWidth Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then Int
0 else Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
sumWidth
let countEW :: Int
countEW = [(Widget, FillLayoutData)] -> Int
forall (t :: * -> *) a a.
(Foldable t, Num a, Functor t) =>
t (a, FillLayoutData) -> a
countExpandedWidgets [(Widget, FillLayoutData)]
filteredWidgets
let expandedW :: Int
expandedW = if Int
countEW Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
0 else Int
deltaW Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
countEW
let restH :: Int
restH = if Int
countEW Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
deltaW else Int
deltaW Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
countEW
[Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets (((Widget, FillLayoutData) -> Widget)
-> [(Widget, FillLayoutData)] -> [Widget]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Widget, FillLayoutData) -> Widget
forall a b. (a, b) -> a
fst [(Widget, FillLayoutData)]
filteredWidgets) [Maybe Int]
widths Int
expandedW Int
restH Int
0
where
drawWidgets :: [Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets [] [Maybe Int]
_ Int
_ Int
_ Int
_ = () -> UIApp u ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
drawWidgets [Widget]
_ [] Int
_ Int
_ Int
_ = () -> UIApp u ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
drawWidgets (Widget
_widget:[Widget]
ws) (Maybe Int
maybeWidth:[Maybe Int]
mws) Int
expandedW Int
restW Int
x =
case Maybe Int
maybeWidth of
Maybe Int
Nothing -> do
let w :: Int
w = Int
expandedW Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int
nat Int
restW
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
forall u.
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
layoutDrawWidget Widget
_widget Drawing
drawing Int
x Int
0 Int
w Int
height
[Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets [Widget]
ws [Maybe Int]
mws Int
expandedW (Int -> Int
dec Int
restW) (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
w)
Just Int
wWidth -> do
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
forall u.
Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
layoutDrawWidget Widget
_widget Drawing
drawing Int
x Int
0 Int
wWidth Int
height
[Widget] -> [Maybe Int] -> Int -> Int -> Int -> UIApp u ()
drawWidgets [Widget]
ws [Maybe Int]
mws Int
expandedW Int
restW (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
wWidth)
countExpandedWidgets :: t (a, FillLayoutData) -> a
countExpandedWidgets t (a, FillLayoutData)
filteredWidgets= t a -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (t a -> a) -> t a -> a
forall a b. (a -> b) -> a -> b
$
(((a, FillLayoutData) -> a) -> t (a, FillLayoutData) -> t a)
-> t (a, FillLayoutData) -> ((a, FillLayoutData) -> a) -> t a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((a, FillLayoutData) -> a) -> t (a, FillLayoutData) -> t a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap t (a, FillLayoutData)
filteredWidgets (((a, FillLayoutData) -> a) -> t a)
-> ((a, FillLayoutData) -> a) -> t a
forall a b. (a -> b) -> a -> b
$ \(a
_, FillLayoutData
layoutData) ->
if FillLayoutData -> Bool
fillLayoutHExpand FillLayoutData
layoutData
then a
1
else a
0
layoutDrawWidget :: Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
layoutDrawWidget :: Widget -> Drawing -> Int -> Int -> Int -> Int -> UIApp u ()
layoutDrawWidget Widget
widget Drawing
drawing Int
x Int
y Int
width Int
height = do
Drawing
d <- Drawing
-> Int
-> Int
-> Int
-> Int
-> ReaderT (AppConfig u) (StateT AppState IO) Drawing
forall (m :: * -> *).
MonadIO m =>
Drawing -> Int -> Int -> Int -> Int -> m Drawing
drawingSliceNew Drawing
drawing Int
x Int
y Int
width Int
height
Widget
-> (Widget -> ListenerList (Drawing -> Int -> Int -> UIApp' ()))
-> (Drawing, Int, Int)
-> UIApp u ()
forall a b w u.
Fire a b =>
w -> (w -> ListenerList a) -> b -> UIApp u ()
fire Widget
widget Widget -> ListenerList (Drawing -> Int -> Int -> UIApp' ())
forall w.
WidgetClass w =>
w -> ListenerList (Drawing -> Int -> Int -> UIApp' ())
draw (Drawing
d, Int
width, Int
height)
fillLayoutVerticalNew :: UIApp u FillLayout
fillLayoutVerticalNew :: UIApp u FillLayout
fillLayoutVerticalNew = FillLayout -> UIApp u FillLayout
forall (m :: * -> *) a. Monad m => a -> m a
return FillLayout
FillLayoutVertical
fillLayoutHorizontalNew :: UIApp u FillLayout
fillLayoutHorizontalNew :: UIApp u FillLayout
fillLayoutHorizontalNew = FillLayout -> UIApp u FillLayout
forall (m :: * -> *) a. Monad m => a -> m a
return FillLayout
FillLayoutHorizontal
dec :: Int -> Int
dec :: Int -> Int
dec Int
x = if Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 then Int
x else Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
nat :: Int -> Int
nat :: Int -> Int
nat Int
x = if Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int
1 else Int
0