module Text.YuiGrid
    (
     HasLayoutHints, modLayoutHints,
     GridElement, GridNode(..),
     gridPage, fromGridNode, runBox, runBoxes,
     setInFstSibling, resetInFstSibling,
     addCss, resetCss, smallMarginBottomCSS, giveBorderCSS,
     inMain, inHeader, inFooter, inLeftSidebar, inRightSidebar,
     nearTop, nearBottom, weight,
     setColumns, setColumnsVote, resetColumns, resetColumnsVote,
     clearSides, nearLeft, nearRight, horizWeight,
     toBox, fromBox, toContainer, fromContainer,
     boxInMain, boxInHeader, boxInFooter, boxInLeftSidebar, boxInRightSidebar,
     applyLayouts,
    )
where

import Text.CxML (CxML, concatCxML, runCxML, showNonCxmlStrict)
import Text.YuiGrid.LayoutHints
import Text.YuiGrid.Grid
import Text.YuiGrid.YGrid
import Text.YuiGrid.YGridCxML

type GridElement a = GridNode (CxML a)

gridPage :: [GridElement a] -> CxML a
gridPage bxs = pageToCxML (yGridPage YPW_950px bxs)

fromGridNode :: GridElement a -> CxML a
fromGridNode (Box cxml _) = cxml
fromGridNode (Container cxmls _) = concatCxML $ map fromGridNode cxmls

runBox :: GridElement a -> a -> GridElement ()
runBox (Box cxml lhs) cx = Box (runCxML cxml cx) lhs
runBox (Container gns lhs) cx = Container (runBoxes gns cx) lhs

runBoxes :: [GridElement a] -> a -> [GridElement ()]
runBoxes ges req = map (`runBox` req) ges