{-# LANGUAGE CPP #-} module MatrixP(matrixP,matrixP') where import Geometry import LayoutRequest import LayoutDir(LayoutDir(..),xc,yc,mkp) import Spacers(Distance) import Defaults(defaultSep) import Data.List(mapAccumL) #ifndef __HBC__ #define fromInt fromIntegral #endif matrixP :: Int -> Placer matrixP Int n = Int -> LayoutDir -> Int -> Placer matrixP' Int n LayoutDir Horizontal forall a. Num a => a defaultSep matrixP' :: Int -> LayoutDir -> Distance -> Placer matrixP' :: Int -> LayoutDir -> Int -> Placer matrixP' Int count' LayoutDir ld Int sep = Placer1 -> Placer P forall a b. (a -> b) -> a -> b $ \ [LayoutRequest] requests -> let n :: Int n = forall (t :: * -> *) a. Foldable t => t a -> Int length [LayoutRequest] requests maxsize :: Point maxsize = ([Point] -> Point pMax forall b c a. (b -> c) -> (a -> b) -> a -> c . (Point originforall a. a -> [a] -> [a] :) forall b c a. (b -> c) -> (a -> b) -> a -> c . forall a b. (a -> b) -> [a] -> [b] map LayoutRequest -> Point minsize) [LayoutRequest] requests rps' :: [Point] rps' = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b] concatMap LayoutRequest -> [Point] refpoints [LayoutRequest] requests maxh :: Int maxh = LayoutDir -> Point -> Int xc LayoutDir ld Point maxsize maxv :: Int maxv = LayoutDir -> Point -> Int yc LayoutDir ld Point maxsize ncols :: Int ncols = Int count' forall a. Ord a => a -> a -> a `min` Int n nrows :: Int nrows = (Int n forall a. Num a => a -> a -> a - Int 1) forall a. Integral a => a -> a -> a `quot` Int count' forall a. Num a => a -> a -> a + Int 1 his :: Int his = Int sep forall a. Num a => a -> a -> a * (Int ncols forall a. Num a => a -> a -> a - Int 1) vis :: Int vis = Int sep forall a. Num a => a -> a -> a * (Int nrows forall a. Num a => a -> a -> a - Int 1) h :: Int h = Int his forall a. Num a => a -> a -> a + Int maxh forall a. Num a => a -> a -> a * Int ncols v :: Int v = Int vis forall a. Num a => a -> a -> a + Int maxv forall a. Num a => a -> a -> a * Int nrows mat2 :: Rect -> [Rect] mat2 (Rect Point gotpos Point gotsize) = let x0 :: Int x0 = LayoutDir -> Point -> Int xc LayoutDir ld Point gotpos y0 :: Int y0 = LayoutDir -> Point -> Int yc LayoutDir ld Point gotpos width :: Int width = LayoutDir -> Point -> Int xc LayoutDir ld Point gotsize height :: Int height = LayoutDir -> Point -> Int yc LayoutDir ld Point gotsize goth,gotv :: Double goth :: Double goth = fromInt (width - his) / fromInt ncols gotv :: Double gotv = fromInt (height - vis) / fromInt nrows pl :: Int -> p -> (Int, Rect) pl Int i p _ = let (Int x, Int y) = (Int i forall a. Integral a => a -> a -> a `rem` Int count', Int i forall a. Integral a => a -> a -> a `quot` Int count') in (Int i forall a. Num a => a -> a -> a + Int 1, Point -> Point -> Rect Rect (LayoutDir -> Int -> Int -> Point mkp LayoutDir ld (Int x0 forall a. Num a => a -> a -> a + forall a b. (RealFrac a, Integral b) => a -> b truncate (fromInt x * (goth + fromInt sep))) (Int y0 forall a. Num a => a -> a -> a + forall a b. (RealFrac a, Integral b) => a -> b truncate (fromInt y * (gotv + fromInt sep)))) (LayoutDir -> Int -> Int -> Point mkp LayoutDir ld (forall a b. (RealFrac a, Integral b) => a -> b truncate Double goth) (forall a b. (RealFrac a, Integral b) => a -> b truncate Double gotv))) in forall a b. (a, b) -> b snd (forall (t :: * -> *) s a b. Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b) mapAccumL forall {p}. Int -> p -> (Int, Rect) pl Int 0 [LayoutRequest] requests) in (Point -> Bool -> Bool -> [Point] -> LayoutRequest refpLayout (LayoutDir -> Int -> Int -> Point mkp LayoutDir ld Int h Int v) Bool False Bool False [Point] rps', Rect -> [Rect] mat2) #ifdef __NHC__ fromInt = fromIntegral #endif