Cascading
This library implements a domain-specific language for cascading style
sheets as used in web pages. It allows you to specify your style sheets
in regular Haskell syntax and gives you all the additional power of
server-side document generation. You can find examples below. To see a
full tutorial, have a look at the Haddock documentation of the
Data.CSS
module.
Current status
Right now most of the CSS 2.1 specification is implemented. In
particular all non-appendix properties now have type-safe Haskell
counterparts in Data.CSS.Properties
.
The type safety goes very far to ensure conformance with the
specification, but some of it has been sacrificed for convenience and
API simplicity.
To do
- Write automated unit tests.
- Write a pretty printer for debugging.
The performance is based on and bound by blaze-builder, so is good
enough for most web applications. For a high-profile web site you may
want to cache the generated stylesheets. The easiest way to do this is
to use regular Haskell sharing. This gets you very close to the best
possible performance:
stylesheet :: ByteString
stylesheet =
toByteString . renderCSS $
{- actual stylesheet -}
If your stylesheet is highly parametric, sharing will not work and you
can use memoization instead. See the memoize, MemoTrie or
monad-memo.
Rendering
To render a stylesheet you can use fromCSS
, renderCSS
or
renderCSST
. All of these will give you a Builder
. You can then use
blaze-builder combinators like toByteString
or toByteStringIO
to
turn it into a ByteString
, send it to a client or write it to a file.
The following example, assuming that stylesheet
is of type Writer CSS ()
, prints the stylesheet to stdout:
import qualified Data.ByteString as B
import Blaze.ByteString.Builder
import Data.CSS
toByteStringIO B.putStr . renderCSS $ stylesheet
Examples
The recommended way to create your stylesheets is to use a writer monad
(transformer). This gives you a large library of predefined properties
covering most of CSS level 2.1.
Basic stylesheets
The following is a basic stylesheet. The imports are listed here for
your convenience, but will be implied in further examples:
import Control.Lens
import Control.Monad.Writer
import Data.Colour
import Data.CSS
import Data.CSS.Properties
stylesheet :: Writer CSS ()
stylesheet =
onAll $ do
select ["p"] $ do
margin . Edges $ [zeroLen]
padding . Edges $ [_Em # 1, _Ex # 2]
select ["em"] $ do
fontWeight BolderWeight
The type signature of stylesheet
is very specialized. The actual type
is more general and makes it easier to interleave your stylesheets with
web framework operations if necessary:
stylesheet :: (MonadWriter CSS m) => m ()
The style sheet will render as:
p {
margin: 0;
padding: 1em 2ex;
}
em {
font-weight: bolder;
}
stylesheet = do
onMedia ["print", "projection"] . select ["p"] $ do
margin . Edges $ [_Em # 0.4, _Ex # 0.1]
padding . Edges $ [zeroLen]
onMedia ["screen"] . select ["p"] $ do
margin . Edges $ [_Em # 0.8, _Ex # 0.4]
padding . Edges $ [zeroLen]
Renders as:
@media print, projection {
p {
margin: 0.4em 0.1ex;
padding: 0;
}
}
@media screen {
p {
margin: 0.8em 0.4ex;
padding: 0;
}
}
Multiple selectors
stylesheet = do
onAll . select ["p", "li"] $ do
margin . Edges $ [_Em # 0.4, _Ex # 0.1]
padding . Edges $ [zeroLen]
below ["em", "strong"] $
fontWeight BolderWeight
Renders as:
p, li {
margin: 0.4em 0.1ex;
padding: 0
}
p em, li em, p strong, li strong {
font-weight: bolder;
}