{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE OverloadedStrings #-}

module Text.XHtml.Frameset.Attributes where

import Text.XHtml.Internals

-- * Extra attributes in XHTML Frameset

frameborder         :: Int    -> HtmlAttr
frameborder :: Int -> HtmlAttr
frameborder         =   Builder -> Int -> HtmlAttr
intAttr Builder
"frameborder"

marginheight        :: Int    -> HtmlAttr
marginheight :: Int -> HtmlAttr
marginheight        =   Builder -> Int -> HtmlAttr
intAttr Builder
"marginheight"

marginwidth         :: Int    -> HtmlAttr
marginwidth :: Int -> HtmlAttr
marginwidth         =   Builder -> Int -> HtmlAttr
intAttr Builder
"marginwidth"

noresize            ::           HtmlAttr
noresize :: HtmlAttr
noresize            = Builder -> HtmlAttr
emptyAttr Builder
"noresize"

scrolling           :: LText -> HtmlAttr
scrolling :: LText -> HtmlAttr
scrolling           =   Builder -> LText -> HtmlAttr
strAttr Builder
"scrolling"