module Placers2(overlayP,
verticalLeftP,verticalLeftP',
horizontalCenterP,horizontalCenterP') where
import LayoutRequest
import Spacers(Distance(..))
import Geometry
import Defaults(defaultSep)
import Data.List(mapAccumL)
import IntMemo
overlayP :: Placer
overlayP :: Placer
overlayP = Placer1 -> Placer
P forall {a}. [LayoutRequest] -> (LayoutRequest, a -> [a])
overlayP'
where
overlayP' :: [LayoutRequest] -> (LayoutRequest, a -> [a])
overlayP' [LayoutRequest]
ls = (LayoutRequest
req,forall {a}. a -> [a]
placer2)
where
ss :: [Size]
ss = forall a b. (a -> b) -> [a] -> [b]
map LayoutRequest -> Size
minsize [LayoutRequest]
ls
rps :: [Size]
rps = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap LayoutRequest -> [Size]
refpoints [LayoutRequest]
ls
wa :: Int -> Size
wa Int
w = Int -> Int -> Size
Point Int
w (forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Int
1forall a. a -> [a] -> [a]
:forall a b. (a -> b) -> [a] -> [b]
map (Size -> Int
ycoord forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip LayoutRequest -> Int -> Size
wAdj Int
w) [LayoutRequest]
ls))
ha :: Int -> Size
ha Int
h = Int -> Int -> Size
Point (forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Int
1forall a. a -> [a] -> [a]
:forall a b. (a -> b) -> [a] -> [b]
map (Size -> Int
xcoord forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> b -> a -> c
flip LayoutRequest -> Int -> Size
hAdj Int
h) [LayoutRequest]
ls)) Int
h
req :: LayoutRequest
req = (Size -> Bool -> Bool -> [Size] -> LayoutRequest
refpLayout ([Size] -> Size
pMax [Size]
ss) (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any LayoutRequest -> Bool
fixedh [LayoutRequest]
ls) (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any LayoutRequest -> Bool
fixedv [LayoutRequest]
ls) [Size]
rps) {wAdj :: Int -> Size
wAdj=forall a. (Int -> a) -> Int -> a
memoInt Int -> Size
wa,hAdj :: Int -> Size
hAdj=forall a. (Int -> a) -> Int -> a
memoInt Int -> Size
ha}
placer2 :: a -> [a]
placer2 a
r = [a
r | LayoutRequest
_ <- [LayoutRequest]
ls]
verticalLeftP :: Placer
verticalLeftP = Int -> Placer
verticalLeftP' forall a. Num a => a
defaultSep
verticalLeftP' :: Distance -> Placer
verticalLeftP' :: Int -> Placer
verticalLeftP' Int
sep = Placer1 -> Placer
P Placer1
vlP
where
vlP :: Placer1
vlP [LayoutRequest]
ls = (LayoutRequest
req,Rect -> [Rect]
placer2)
where
req :: LayoutRequest
req = (Size -> Bool -> Bool -> [Size] -> LayoutRequest
refpLayout (Int -> Int -> Size
Point Int
w Int
h) Bool
False (forall (t :: * -> *). Foldable t => t Bool -> Bool
and [Bool]
fvs) (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Size]]
rpss)) {wAdj :: Int -> Size
wAdj=forall a. (Int -> a) -> Int -> a
memoInt Int -> Size
wa}
wa :: Int -> Size
wa Int
aw = Int -> Int -> Size
Point Int
aw (forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
hsforall a. Num a => a -> a -> a
+Int
totsep)
where hs :: [Int]
hs = [Size -> Int
ycoord (Int -> Size
wAdj (forall a. Ord a => a -> a -> a
min Int
aw Int
w)) | Layout{minsize :: LayoutRequest -> Size
minsize=Point Int
w Int
_,wAdj :: LayoutRequest -> Int -> Size
wAdj=Int -> Size
wAdj}<-[LayoutRequest]
ls]
totsep :: Int
totsep = Int
sepforall a. Num a => a -> a -> a
*(forall (t :: * -> *) a. Foldable t => t a -> Int
length [LayoutRequest]
lsforall a. Num a => a -> a -> a
-Int
1)
([Size]
ss,[Bool]
fhs,[Bool]
fvs) = [LayoutRequest] -> ([Size], [Bool], [Bool])
unzipsfhv [LayoutRequest]
ls
([Int]
ws,[Int]
hs) = forall a b. [(a, b)] -> ([a], [b])
unzip [(Int
w,Int
h) | Point Int
w Int
h <- [Size]
ss]
w :: Int
w = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Int
1forall a. a -> [a] -> [a]
:[Int]
ws)
h :: Int
h = forall a. Ord a => a -> a -> a
max Int
1 (Int
h'forall a. Num a => a -> a -> a
-Int
sep)
(Int
h',[[Size]]
rpss) = forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL Int -> LayoutRequest -> (Int, [Size])
adjust Int
0 [LayoutRequest]
ls
where adjust :: Int -> LayoutRequest -> (Int, [Size])
adjust Int
y (Layout {minsize :: LayoutRequest -> Size
minsize=Point Int
_ Int
rh,refpoints :: LayoutRequest -> [Size]
refpoints=[Size]
rps}) =
(Int
yforall a. Num a => a -> a -> a
+Int
rhforall a. Num a => a -> a -> a
+Int
sep,forall a b. (a -> b) -> [a] -> [b]
map Size -> Size
adj1 [Size]
rps)
where adj1 :: Size -> Size
adj1 (Point Int
rx Int
ry) = Int -> Int -> Size
Point Int
rx (Int
yforall a. Num a => a -> a -> a
+Int
ry)
placer2 :: Rect -> [Rect]
placer2 (Rect (Point Int
x0 Int
y0) Size
_) = [Int] -> [Size] -> Int -> [Rect]
placer2' [Int]
hs [Size]
ss Int
y0
where placer2' :: [Int] -> [Size] -> Int -> [Rect]
placer2' (Int
h:[Int]
hs) (Size
s:[Size]
ss) Int
y =
Size -> Size -> Rect
Rect (Int -> Int -> Size
Point Int
x0 Int
y) Size
sforall a. a -> [a] -> [a]
:[Int] -> [Size] -> Int -> [Rect]
placer2' [Int]
hs [Size]
ss (Int
yforall a. Num a => a -> a -> a
+Int
sepforall a. Num a => a -> a -> a
+Int
h)
placer2' [Int]
_ [Size]
_ Int
_ = []
horizontalCenterP :: Placer
horizontalCenterP = Int -> Placer
horizontalCenterP' forall a. Num a => a
defaultSep
horizontalCenterP' :: Distance -> Placer
horizontalCenterP' :: Int -> Placer
horizontalCenterP' Int
sep = Placer1 -> Placer
P Placer1
hcP
where
hcP :: Placer1
hcP [LayoutRequest]
ls = (LayoutRequest
req,Rect -> [Rect]
placer2)
where
req :: LayoutRequest
req = (Size -> Bool -> Bool -> [Size] -> LayoutRequest
refpLayout (Int -> Int -> Size
Point Int
w Int
h) (forall (t :: * -> *). Foldable t => t Bool -> Bool
and [Bool]
fhs) Bool
False (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Size]]
rpss)) {hAdj :: Int -> Size
hAdj=forall a. (Int -> a) -> Int -> a
memoInt Int -> Size
ha}
([Size]
ss,[Bool]
fhs,[Bool]
fvs) = [LayoutRequest] -> ([Size], [Bool], [Bool])
unzipsfhv [LayoutRequest]
ls
ha :: Int -> Size
ha Int
ah = Int -> Int -> Size
Point (forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
wsforall a. Num a => a -> a -> a
+Int
totsep) Int
ah
where ws :: [Int]
ws = [Size -> Int
xcoord (Int -> Size
hAdj (forall a. Ord a => a -> a -> a
min Int
ah Int
h)) | Layout{minsize :: LayoutRequest -> Size
minsize=Point Int
_ Int
h,hAdj :: LayoutRequest -> Int -> Size
hAdj=Int -> Size
hAdj}<-[LayoutRequest]
ls]
totsep :: Int
totsep = Int
sepforall a. Num a => a -> a -> a
*(forall (t :: * -> *) a. Foldable t => t a -> Int
length [LayoutRequest]
lsforall a. Num a => a -> a -> a
-Int
1)
([Int]
ws,[Int]
hs) = forall a b. [(a, b)] -> ([a], [b])
unzip [(Int
w,Int
h) | Point Int
w Int
h <- [Size]
ss]
w :: Int
w = forall a. Ord a => a -> a -> a
max Int
1 Int
w'
h :: Int
h = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Int
1forall a. a -> [a] -> [a]
:[Int]
hs)
(Int
w',[[Size]]
rpss) = forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL Int -> LayoutRequest -> (Int, [Size])
adjust Int
0 [LayoutRequest]
ls
where adjust :: Int -> LayoutRequest -> (Int, [Size])
adjust Int
x (Layout {minsize :: LayoutRequest -> Size
minsize=Point Int
rw Int
rh,refpoints :: LayoutRequest -> [Size]
refpoints=[Size]
rps}) =
(Int
xforall a. Num a => a -> a -> a
+Int
rwforall a. Num a => a -> a -> a
+Int
sep,forall a b. (a -> b) -> [a] -> [b]
map Size -> Size
adj1 [Size]
rps)
where adj1 :: Size -> Size
adj1 (Point Int
rx Int
ry) = Int -> Int -> Size
Point (Int
xforall a. Num a => a -> a -> a
+Int
rx) (Int
ryforall a. Num a => a -> a -> a
+(Int
hforall a. Num a => a -> a -> a
-Int
rh) forall a. Integral a => a -> a -> a
`div` Int
2)
placer2 :: Rect -> [Rect]
placer2 (Rect (Point Int
x0 Int
y0) (Point Int
_ Int
ah)) = [Int] -> [Int] -> [Size] -> Int -> [Rect]
placer2' [Int]
ws [Int]
hs [Size]
ss Int
x0
where placer2' :: [Int] -> [Int] -> [Size] -> Int -> [Rect]
placer2' (Int
w:[Int]
ws) (Int
h:[Int]
hs) (Size
s:[Size]
ss) Int
x =
Size -> Size -> Rect
Rect (Int -> Int -> Size
Point Int
x (Int
y0forall a. Num a => a -> a -> a
+(Int
ahforall a. Num a => a -> a -> a
-Int
h) forall a. Integral a => a -> a -> a
`div` Int
2)) Size
sforall a. a -> [a] -> [a]
:[Int] -> [Int] -> [Size] -> Int -> [Rect]
placer2' [Int]
ws [Int]
hs [Size]
ss (Int
xforall a. Num a => a -> a -> a
+Int
sepforall a. Num a => a -> a -> a
+Int
w)
placer2' [Int]
_ [Int]
_ [Size]
_ Int
_ = []
unzipsfhv :: [LayoutRequest] -> ([Size], [Bool], [Bool])
unzipsfhv [LayoutRequest]
ls =
forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip3 [(Size
s,Bool
fh,Bool
fv) | Layout {minsize :: LayoutRequest -> Size
minsize=Size
s,fixedh :: LayoutRequest -> Bool
fixedh=Bool
fh,fixedv :: LayoutRequest -> Bool
fixedv=Bool
fv} <- [LayoutRequest]
ls]