module Graphics.Layout.Grid where import Data.Text (Text) import Data.List (intersperse) import Graphics.Layout.Box as B data Grid m n = Grid { rows :: [(Name, Either m Double)], columns :: [(Name, Either n Double)], gap :: Size m n, gridBox :: PaddedBox m n } data GridItem m n = GridItem { startRow :: Int, endRow :: Int, startCol :: Int, endCol :: Int, gridItemBox :: PaddedBox m n } type Name = Text cellsForCol :: [GridItem y x] -> Int -> [GridItem y x] cellsForCol cells ix = [cell | cell <- cells, startCol cell == ix, startCol cell /= endCol cell] cellsForRow :: [GridItem y x] -> Int -> [GridItem y x] cellsForRow cells ix = [cell | cell <- cells, startRow cell == ix, startRow cell /= endRow cell] {-gridEstWidth :: Grid y Length -> [GridItem y Double] -> Double-} gridMinWidths :: Double -> Grid y Length -> [GridItem y Double] -> (Double, [Double]) gridMinWidths parent self childs = (sum $ intersperse (lowerLength parent $ inline $ gap self) ret, ret) where ret = map colMinWidth $ enumerate $ map snd $ columns self colMinWidth (_, Left (Pixels x)) = x colMinWidth (_, Left (Percent x)) = x * parent colMinWidth arg@(ix, Left Preferred) = maximum $ map (inline . size . gridItemBox) $ cellsForCol childs ix colMinWidth (ix, _) = maximum $ map (inline . B.min . gridItemBox) $ cellsForCol childs ix gridNatWidths :: Double -> Grid y Length -> [GridItem y Double] -> (Double, [Double]) gridNatWidths parent self childs = (sum $ intersperse (lowerLength parent $ inline $ gap self) ret, ret) where ret = map colNatWidth $ enumerate $ map snd $ columns self colNatWidth (_, Left (Pixels x)) = x colNatWidth (_, Left (Percent x)) = x * parent colNatWidth arg@(ix, Left Min) = maximum $ map (inline . B.min . gridItemBox) $ cellsForCol childs ix colNatWidth (ix, _) = maximum $ map (inline . size . gridItemBox) $ cellsForCol childs ix gridMaxWidths :: PaddedBox y Double -> Grid y Length -> [(Double, Double)] -> (Double, [Double]) gridMaxWidths parent self subwidths = (sum $ intersperse (lowerLength outerwidth $ inline $ gap self) ret, ret) where ret = map (colMaxWidth fr) $ zip subwidths $ map snd $ columns self fr = (outerwidth - estimate)/(countFRs $ map snd $ columns self) outerwidth = inline $ size parent estimate = sum $ intersperse (lowerLength outerwidth $ inline $ gap self) $ map (colMaxWidth 0) $ zip subwidths $ map snd $ columns self colMaxWidth _ (_, Left (Pixels x)) = x colMaxWidth _ (_, Left (Percent x)) = x colMaxWidth _ ((_, nat), Left Preferred) = nat colMaxWidth _ ((min, _), Left Min) = min colMaxWidth fr (_, Left Auto) = fr colMaxWidth fr (_, Right x) = x*fr countFRs (Left Auto:rest) = succ $ countFRs rest countFRs (Right x:rest) = x + countFRs rest countFRs [] = 0 {-gridWidths :: PaddedBox y Double -> Grid y Length -> (Double, [Double]) gridNatHeights :: PaddedBox Length Double -> [GridItem Length Double] -> (Double, [Double]) gridMinHeights :: Double -> Grid Length Double -> (Double, [Double]) gridMaxHeights :: Double -> Grid Length Double -> (Double, [Double]) gridHeights :: Double -> Grid Length Double -> (Double, [Double]) gridPosition :: GridLength Double Double -> [GridItem Double Double] -> [Size Double Double] gridLayout :: PaddedBox Double Double -> Grid Length Length -> [GridItem Length Length] -> Bool -> (Grid Double Double, [(Size Double Double, GridItem Double Double)])-} enumerate = zip [0..]