Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is the twin brother of module Text.Cassius. The difference is that these parsers preserv the given order of attributes and mixin blocks.
let bams = [cassiusMixin| bam1:bam2 ^{bins} bam3:bam4 |] :: Mixin bins = [cassiusMixin| bin1:bin2 |] :: Mixin in renderCss ([Text.Ordered.lucius|foo{bar1:bar2;^{bams};bar3:bar4;}|] undefined) "foo{bar1:bar2;bam1:bam2;bin1:bin2;bam3:bam4;bar3:bar4}"
Synopsis
- data Css
- type CssUrl url = (url -> [(Text, Text)] -> Text) -> Css
- class ToCss a where
- renderCss :: Css -> Text
- renderCssUrl :: (url -> [(Text, Text)] -> Text) -> CssUrl url -> Text
- cassius :: QuasiQuoter
- cassiusFile :: FilePath -> Q Exp
- cassiusFileDebug :: FilePath -> Q Exp
- cassiusFileReload :: FilePath -> Q Exp
- cassiusMixin :: QuasiQuoter
- data Mixin
- data Color = Color Word8 Word8 Word8
- colorRed :: Color
- colorBlack :: Color
- mkSize :: String -> ExpQ
- data AbsoluteUnit
- = Centimeter
- | Inch
- | Millimeter
- | Pica
- | Point
- data AbsoluteSize = AbsoluteSize {}
- absoluteSize :: AbsoluteUnit -> Rational -> AbsoluteSize
- data EmSize = EmSize Rational
- data ExSize = ExSize Rational
- data PercentageSize = PercentageSize {}
- percentageSize :: Rational -> PercentageSize
- data PixelSize = PixelSize Rational
- cassiusUsedIdentifiers :: String -> [(Deref, VarType)]
Datatypes
Type class
Instances
ToCss Text Source # | |
ToCss Text Source # | |
ToCss PercentageSize Source # | |
Defined in Text.Internal.CssCommon toCss :: PercentageSize -> Builder Source # | |
ToCss AbsoluteSize Source # | |
Defined in Text.Internal.CssCommon toCss :: AbsoluteSize -> Builder Source # | |
ToCss Color Source # | |
ToCss EmSize Source # | |
ToCss ExSize Source # | |
ToCss PixelSize Source # | |
ToCss [Char] Source # | |
Rendering
Parsing
cassius :: QuasiQuoter Source #
Since: 2.0.30
Mixims
cassiusMixin :: QuasiQuoter Source #
Create a mixin with Cassius syntax.
| @since 2.0.30
ToCss instances
Color
colorBlack :: Color Source #
Size
data AbsoluteUnit Source #
Absolute size units.
Instances
Eq AbsoluteUnit Source # | |
Defined in Text.Internal.CssCommon (==) :: AbsoluteUnit -> AbsoluteUnit -> Bool # (/=) :: AbsoluteUnit -> AbsoluteUnit -> Bool # | |
Show AbsoluteUnit Source # | |
Defined in Text.Internal.CssCommon showsPrec :: Int -> AbsoluteUnit -> ShowS # show :: AbsoluteUnit -> String # showList :: [AbsoluteUnit] -> ShowS # |
data AbsoluteSize Source #
Not intended for direct use, see mkSize
.
AbsoluteSize | |
|
Instances
absoluteSize :: AbsoluteUnit -> Rational -> AbsoluteSize Source #
Constructs AbsoluteSize
. Not intended for direct use, see mkSize
.
data PercentageSize Source #
Not intended for direct use, see mkSize
.
PercentageSize | |
|
Instances
percentageSize :: Rational -> PercentageSize Source #
Constructs PercentageSize
. Not intended for direct use, see mkSize
.