module Text.YuiGrid.YGrid where import Text.CxML (CssInlineDecl) import Text.YuiGrid.LayoutHints import Text.YuiGrid.Grid data YPage a = YPage { pageWidth :: YPageWidth, headerBlock :: [YGrid a], mainBlock :: [YGrid a], footerBlock :: [YGrid a], sidebarBlock :: Maybe (YTemplate, [YGrid a]) } -- body is made from mainBlock and sidebarBlock -- if there are no header and footer, just blocks can be rendered (no header, no footer, no body) -- if there is no sidebar, blocks don't need to be render, but header and body and footer might need to be rendered data YPageWidth = YPW_750px -- #doc - 750px centered (good for 800x600) | YPW_950px -- #doc2 - 950px centered (good for 1024x768) | YPW_100perc -- #doc3 - 100% fluid (good for everybody) | YPW_974px -- #doc4 - 974px fluid (good for 1024x768) -- YPW_Custom -- #doc-custom - an example of a custom page width data YTemplate = SidebarLeft_160px | SidebarLeft_180px | SidebarLeft_300px | SidebarRight_180px | SidebarRight_240px | SidebarRight_300px data YGrid a = YGrid_SimpleBox a [CssInlineDecl] | YGrid_ComplexBox [YGrid a] [CssInlineDecl] | YGrid_1Col [YGrid a] | YGrid_2Cols Y_2ColsType [YGrid a] [YGrid a] | YGrid_3Cols [YGrid a] [YGrid a] [YGrid a] -- .yui-gb - Special grid, 1/3 - 1/3 - 1/3 data Y_2ColsType = Y_1o2_1o2 -- .yui-g - Standard half grid (and nest again for quarters) | Y_2o3_1o3 -- .yui-gc - Special grid, 2/3 - 1/3 | Y_1o3_2o3 -- .yui-gd - Special grid, 1/3 - 2/3 | Y_3o4_1o4 -- .yui-ge - Special grid, 3/4 - 1/4 | Y_1o4_3o4 -- .yui-gf - Special grid, 1/4 - 3/4 -- for the recursive YGrid cases, in case that any of the YGrid children is not subdivided, it will be rendered as a unit, -- in case it is subdivided, it will be rendered as a grid. -- the first child of multi-column grids will be annotated with first, it doesn't matter whether is a unit or grid itself. yGridPage :: YPageWidth -> [GridNode a] -> YPage a yGridPage pageWidth gns = case (leftSidebarGNodes, rightSidebarGNodes) of ([],[]) -> YPage pageWidth yHeader yBody yFooter Nothing -- no sidebars (_,[]) -> YPage pageWidth yHeader yBody yFooter (Just (SidebarLeft_160px, yLeftSidebar)) -- left sidebar using template ([],_) -> YPage pageWidth yHeader yBody yFooter (Just (SidebarRight_180px, yRightSidebar)) -- right sidebar using template _ -> YPage pageWidth yHeader yBodyWithRightSidebar yFooter (Just (SidebarLeft_160px, yLeftSidebar)) -- left sidebar using template, right encoded in body where (mainGNodes, headerGNodes, footerGNodes, leftSidebarGNodes, rightSidebarGNodes) = gridNodesByPageArea gns yHeader = yGridStack headerGNodes yFooter = yGridStack footerGNodes yLeftSidebar = yGridStack leftSidebarGNodes yRightSidebar = yGridStack rightSidebarGNodes yBody = yGridStack mainGNodes yBodyWithRightSidebar = [YGrid_2Cols Y_3o4_1o4 yBody yRightSidebar] yGridStack = yGrids Nothing yGrid :: GridNode a -> YGrid a yGrid (Box x lhs) = YGrid_SimpleBox x (cssHints lhs) yGrid gn@(Container gns lhs) = YGrid_ComplexBox (yGrids (columnsQty lhs) gns) (cssHints lhs) yGrids :: Maybe Int -> [GridNode a] -> [YGrid a] yGrids colSpec = map (yGridCols . gridNodesByColumns colSpec) . splitClearSides . gridNodesVerticalPartitions yGridCols :: [[GridNode a]] -> YGrid a yGridCols cols = yGridCols' (map (map yGrid) cols) yGridCols' :: [[YGrid a]] -> YGrid a yGridCols' [col1] = YGrid_1Col col1 yGridCols' [col1,col2] = yGrid_2Col col1 col2 yGridCols' [col1,col2,col3] = YGrid_3Cols col1 col2 col3 yGridCols' [col1,col2,col3,col4] = yGrid_2Col [yGrid_2Col col1 col2] [yGrid_2Col col3 col4] yGridCols' cols = YGrid_1Col (concat cols) yGrid_2Col = YGrid_2Cols Y_1o2_1o2