Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- luciusWithOrder :: Order -> QuasiQuoter
- luciusFromString :: Order -> String -> Q Exp
- whiteSpace :: Parser ()
- whiteSpace1 :: Parser ()
- parseBlock :: Order -> Parser (Block 'Unresolved)
- detectAmp :: Block 'Unresolved -> (Bool, Block 'Unresolved)
- partitionPBs :: Order -> [PairBlock] -> ([Either (Attr 'Unresolved) Deref], [Block 'Unresolved])
- parseSelector :: Parser [Contents]
- trim :: Contents -> Contents
- data PairBlock
- parsePairsBlocks :: Order -> ([PairBlock] -> [PairBlock]) -> Parser [PairBlock]
- parsePair :: Parser (Attr 'Unresolved)
- parseContents :: String -> Parser Contents
- parseContent :: String -> Parser Content
- isHex :: Char -> Bool
- atMost :: Int -> Parser a -> Parser [a]
- parseComment :: Parser Content
- luciusFileWithOrd :: Order -> FilePath -> Q Exp
- luciusFileDebugWithOrder :: Order -> FilePath -> Q Exp
- parseTopLevels :: Order -> Parser [TopLevel 'Unresolved]
- stringCI :: String -> Parser ()
- luciusRTWithOrder' :: Order -> Text -> Either String ([(Text, Text)] -> Either String [TopLevel 'Resolved])
- luciusRTInternal :: Order -> Text -> Either String ([(Text, RTValue)] -> Either String [TopLevel 'Resolved])
- luciusRTWithOrder :: Order -> Text -> [(Text, Text)] -> Either String Text
- luciusRTMixinWithOrder :: Order -> Text -> Bool -> [(Text, RTValue)] -> Either String Text
- data RTValue
- luciusRTMinifiedWithOrder :: Order -> Text -> [(Text, Text)] -> Either String Text
- luciusUsedIdentifiers :: Order -> String -> [(Deref, VarType)]
- luciusMixinWithOrder :: Order -> QuasiQuoter
- luciusMixinFromString :: Order -> String -> Q Exp
Documentation
luciusWithOrder :: Order -> QuasiQuoter Source #
whiteSpace :: Parser () Source #
whiteSpace1 :: Parser () Source #
parseBlock :: Order -> Parser (Block 'Unresolved) Source #
detectAmp :: Block 'Unresolved -> (Bool, Block 'Unresolved) Source #
Looks for an & at the beginning of a selector and, if present, indicates that we should not have a leading space. Otherwise, we should have the leading space.
partitionPBs :: Order -> [PairBlock] -> ([Either (Attr 'Unresolved) Deref], [Block 'Unresolved]) Source #
parseSelector :: Parser [Contents] Source #
parseContents :: String -> Parser Contents Source #
parseContent :: String -> Parser Content Source #
parseComment :: Parser Content Source #
parseTopLevels :: Order -> Parser [TopLevel 'Unresolved] Source #
luciusRTInternal :: Order -> Text -> Either String ([(Text, RTValue)] -> Either String [TopLevel 'Resolved]) Source #
luciusUsedIdentifiers :: Order -> String -> [(Deref, VarType)] Source #
Determine which identifiers are used by the given template, useful for creating systems like yesod devel.
luciusMixinWithOrder :: Order -> QuasiQuoter Source #