cascading-0.1.0: DSL for HTML CSS (Cascading Style Sheets)

MaintainerErtugrul Soeylemez <es@ertes.de>
Safe HaskellNone

Data.CSS

Contents

Description

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.

Synopsis

Tutorial

Style sheets are values of type CSS. This type denotes style sheets, including for different media and is itself a monoid, so that you can build your style sheets either in a chunk-by-chunk fashion or using a writer monad. The latter is the recommended way, because it gives you access to a large library of predefined properties with additional type safety. It is recommended to enable the OverloadedStrings extension for this library and is assumed for the rest of this tutorial.

Style properties are usually specified by using the predefined property writers:

 display InlineDisplay
 direction LeftToRight
 float LeftFloat

If a property is not pre-defined you can set it by using setProp or its infix variant $=.

 setProp "font-family" ("times" :: PropValue)
 "text-decoration" $= ("underline" :: PropValue)

The type signatures are necessary because the property value is actually polymorphic and needs to be an instance of ToPropValue. There are many predefined instances:

 "z-index" $= 15
 "margin"  $= ["1em", "2px"]

These values will render as 15 and 1em 2px respectively.

Selectors and media

In order to specify properties you first need to establish media types and selectors. The simplest way to do this is to use onAll, onMedia and select:

 stylesheet :: Writer CSS ()
 stylesheet =
     onAll . select ["p"] $ do
         lineHeight . Just $ _Cm # 1
         zIndex Nothing
         borderStyle . LeftEdge $ SolidBorder

This will render as the following stylesheet:

 p {
     line-height: 10mm;
     z-index: auto;
     border-left-style: solid;
 }

To restrict the media to which the stylesheet applies just use onMedia instead of onAll:

 onMedia ["print"] . select ["p"] $ ...

This will render as:

 @media print {
     p { /* ... */ }
 }

Often it is convenient to specify properties for elements below the current selection. You can use the below combinator to do this:

 onAll . select ["p"] $ do
     lineHeight . Just $ _Cm # 1
     zIndex Nothing

     below ["em"] $ do
         margin . Edges $ [_Em # 0.2, _Ex # 1]
         padding . Edges $ [_Em # 0.1, _Ex # 0.5]

The inner block specifies properties for p em, so the above will render as the following stylesheet:

 p {
     line-height: 10mm;
     z-index: auto;
 }

 p em {
     margin: 0.2em 1ex;
     padding: 0.1em 0.5ex;
 }

You can also specify properties for multiple selectors simultaneously:

 onAll . select ["html", "body"] $ do
     margin . Edges $ [zeroLen]
     padding . Edges $ [_Em # 1, _Ex # 2]

     below ["a", "p"] $ do
         backgroundColor black
         color limegreen

This renders as the following stylesheet:

 html, body {
     margin: 0;
     padding: 1em 2ex;
 }

 html a, body a, html p, body p {
     background-color: #000;
     color: #32cd32;
 }

Rendering

To render a stylesheet you can use fromCSS, renderCSS or renderCSST. All of these will give you a Builder. You can then use combinators like toByteString or toByteStringIO to turn it into a ByteString, send it to a client or write it to a file.

The lowest level function is fromCSS, which will take a CSS value and give you a Builder:

 fromCSS :: CSS -> Builder

The most convenient way to write your stylesheets is to use a writer monad, in which case you would use one of these functions instead, depending on the shape of your monad:

 renderCSS  :: Writer CSS a -> Builder
 renderCSST :: (Monad m) => WriterT CSS m a -> m Builder

The following example prints the stylesheet to stdout, assuming stylesheet is of type Writer CSS ():

 import qualified Data.ByteString as B

 toByteStringIO B.putStr . renderCSS $ stylesheet

Lengths

For convenience lengths can and should be specified by using predefined prisms like _Cm (see HasLength):

 lineHeight $ Just (_Cm # 1)

This will render as line-height: 10mm. All compatible lengths are saved and rendered in a canonical unit. For example centimeters, millimeters, inches, picas and points are all rendered as their correspondingly scaled millimeter lengths, i.e. _In # 1 will render as 25.4mm.

For convenience there are also two ways to specify percental lengths. The lengths _Percent # 150 and _Factor # 1.5 are equivalent and both render as 150%.

There are also two special lengths, zeroLen and autoLen, which render as 0 and auto respectively.

Colors

Colors are specified by using the Colour and AlphaColour types from the colour library. They are rendered as either #rgb, #rrggbb or rgba(r,g,b,a) depending on what color you specify and whether it is fully opaque. The following renders as border-left-color: #0f0:

 import Data.Colour.Names

 borderColor (LeftEdge lime)

The colour library gives you both correct color space handling, sensible operators for mixing colors and a large library of predefined colors in the Data.Colour.Names module. To mix two colors you can use blend for mixing or over for alpha blending:

 blend 0.5 lime red
 (lime `withOpacity` 0.5) `over` black

Colors are all rendered in the (non-linear) sRGB color space, as this is the assumed color space by most user agents and screens.

Edge-oriented properties

Many CSS properties are edge-oriented, for example margin, padding and borderColor. This library provides a unified interface to these properties through the Edge type. Examples:

 margin . BottomEdge $ _Mm # 1  -- margin-bottom: 1mm
 margin . LeftEdge $ _Mm # 1    -- margin-left: 1mm
 margin . RightEdge $ _Mm # 1   -- margin-right: 1mm
 margin . TopEdge $ _Mm # 1     -- margin-top: 1mm

To set all edges through the margin property just use the Edges constructor:

 margin . Edges $ [_Mm # 2, _Mm # 1]  -- margin: 2mm 1mm
 margin . Edges $ [_Mm # 5]           -- margin: 5mm

You can also use the usual monadic combinators:

 mapM_ margin [LeftEdge (_Mm # 3),
               RightEdge (_Mm # 4)]

Imports

To import an external stylesheet you can use importFrom or importUrl. The former allows you to specify raw URLs:

 importFrom "screen" "/style/screen.css"

In web frameworks like Happstack you would usually work on top of a MonadRoute-based monad (like RouteT) as defined in the web-routes library. In this case the importUrl function allows you to use your type-safe URLs conveniently:

 importUrl "all" (Style "screen")

To import a stylesheet for multiple media types, just use the import functions multiple times for the same URL:

 mapM_ (`importFrom` "/style/screen.css") ["screen", "print"]

This will render as:

 @import url("/style/screen.css") print, screen;

Miscellaneous

Important properties

To set the !important tag on a property you can use the important function:

 important (display InlineDisplay)

This renders as:

 display: inline !important;

Inheriting

To inherit a property value use inherit. You have to spell out the property name in this case:

 inherit "display"

This renders as:

 display: inherit;

Optimizations

The underlying representation is a straightforward list of selectors and properties. There may be closer or more efficient representations, but all of them need to make some compromises along the way. Consider the following stylesheet:

 p {
     border-color: #0f0;
     border-color: rgba(0, 255, 0, 1);
 }

You can optimize this to a single property, but which one? It depends on whether the user agent supports CSS level 3, so we would need to make assumptions. We also can't use a map of properties to a list of values. Consider the following stylesheet:

 p {
     border-bottom-color: #0f0;
     border-color: #f00;
 }

The order of the properties does matter here, so we need to preserve it. This rules out a map from properties to lists of values. The final question is: Can we use a map from selectors to property lists? As it turns out no, because CSS specificity does not always apply:

 a:link { /* ... */ }
 a:blah { /* ... */ }

These two selectors have the same specificity. CSS allows unsupported pseudo-classes and user agents must ignore them, so in edge cases the order can matter.

Other than media types CSS does not seem to exhibit any commutativity, so we use regular lists. Also since most authors use mostly hand-written stylesheets with little property overlap the list representation is usually faster anyway, so this choice seems to be sensible.

The only optimization performed by this library is the minified output it produces. Pretty-printing is currently not supported.

Reexports