{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleInstances #-}
module Text.Hamlet.Parse
( Result (..)
, Content (..)
, Doc (..)
, parseDoc
, HamletSettings (..)
, defaultHamletSettings
, xhtmlHamletSettings
, CloseStyle (..)
, Binding (..)
, NewlineStyle (..)
, specialOrIdent
, DataConstr (..)
, Module (..)
)
where
import Text.Shakespeare.Base
import Control.Applicative ((<$>), Applicative (..))
import Control.Monad
import Control.Arrow
import Data.Char (GeneralCategory(..), generalCategory, isUpper)
import Data.Data
import Text.ParserCombinators.Parsec hiding (Line)
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Maybe (mapMaybe, fromMaybe, isNothing)
import Language.Haskell.TH.Syntax hiding (Module)
data Result v = Error String | Ok v
deriving (Int -> Result v -> ShowS
forall v. Show v => Int -> Result v -> ShowS
forall v. Show v => [Result v] -> ShowS
forall v. Show v => Result v -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Result v] -> ShowS
$cshowList :: forall v. Show v => [Result v] -> ShowS
show :: Result v -> String
$cshow :: forall v. Show v => Result v -> String
showsPrec :: Int -> Result v -> ShowS
$cshowsPrec :: forall v. Show v => Int -> Result v -> ShowS
Show, Result v -> Result v -> Bool
forall v. Eq v => Result v -> Result v -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Result v -> Result v -> Bool
$c/= :: forall v. Eq v => Result v -> Result v -> Bool
== :: Result v -> Result v -> Bool
$c== :: forall v. Eq v => Result v -> Result v -> Bool
Eq, ReadPrec [Result v]
ReadPrec (Result v)
ReadS [Result v]
forall v. Read v => ReadPrec [Result v]
forall v. Read v => ReadPrec (Result v)
forall v. Read v => Int -> ReadS (Result v)
forall v. Read v => ReadS [Result v]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Result v]
$creadListPrec :: forall v. Read v => ReadPrec [Result v]
readPrec :: ReadPrec (Result v)
$creadPrec :: forall v. Read v => ReadPrec (Result v)
readList :: ReadS [Result v]
$creadList :: forall v. Read v => ReadS [Result v]
readsPrec :: Int -> ReadS (Result v)
$creadsPrec :: forall v. Read v => Int -> ReadS (Result v)
Read, Result v -> DataType
Result v -> Constr
forall {v}. Data v => Typeable (Result v)
forall v. Data v => Result v -> DataType
forall v. Data v => Result v -> Constr
forall v.
Data v =>
(forall b. Data b => b -> b) -> Result v -> Result v
forall v u.
Data v =>
Int -> (forall d. Data d => d -> u) -> Result v -> u
forall v u.
Data v =>
(forall d. Data d => d -> u) -> Result v -> [u]
forall v r r'.
Data v =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
forall v r r'.
Data v =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
forall v (m :: * -> *).
(Data v, Monad m) =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
forall v (m :: * -> *).
(Data v, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
forall v (c :: * -> *).
Data v =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Result v)
forall v (c :: * -> *).
Data v =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Result v -> c (Result v)
forall v (t :: * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Result v))
forall v (t :: * -> * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Result v))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Result v)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Result v -> c (Result v)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Result v))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
$cgmapMo :: forall v (m :: * -> *).
(Data v, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
$cgmapMp :: forall v (m :: * -> *).
(Data v, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
$cgmapM :: forall v (m :: * -> *).
(Data v, Monad m) =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Result v -> u
$cgmapQi :: forall v u.
Data v =>
Int -> (forall d. Data d => d -> u) -> Result v -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Result v -> [u]
$cgmapQ :: forall v u.
Data v =>
(forall d. Data d => d -> u) -> Result v -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
$cgmapQr :: forall v r r'.
Data v =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
$cgmapQl :: forall v r r'.
Data v =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
gmapT :: (forall b. Data b => b -> b) -> Result v -> Result v
$cgmapT :: forall v.
Data v =>
(forall b. Data b => b -> b) -> Result v -> Result v
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Result v))
$cdataCast2 :: forall v (t :: * -> * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Result v))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Result v))
$cdataCast1 :: forall v (t :: * -> *) (c :: * -> *).
(Data v, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Result v))
dataTypeOf :: Result v -> DataType
$cdataTypeOf :: forall v. Data v => Result v -> DataType
toConstr :: Result v -> Constr
$ctoConstr :: forall v. Data v => Result v -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Result v)
$cgunfold :: forall v (c :: * -> *).
Data v =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Result v)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Result v -> c (Result v)
$cgfoldl :: forall v (c :: * -> *).
Data v =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Result v -> c (Result v)
Data, Typeable)
instance Monad Result where
return :: forall a. a -> Result a
return = forall a. a -> Result a
Ok
Error String
s >>= :: forall a b. Result a -> (a -> Result b) -> Result b
>>= a -> Result b
_ = forall v. String -> Result v
Error String
s
Ok a
v >>= a -> Result b
f = a -> Result b
f a
v
#if MIN_VERSION_base(4,13,0)
instance MonadFail Result where
fail :: forall v. String -> Result v
fail = forall v. String -> Result v
Error
#endif
instance Functor Result where
fmap :: forall a b. (a -> b) -> Result a -> Result b
fmap = forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM
instance Applicative Result where
pure :: forall a. a -> Result a
pure = forall (m :: * -> *) a. Monad m => a -> m a
return
<*> :: forall a b. Result (a -> b) -> Result a -> Result b
(<*>) = forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
data Content = ContentRaw String
| ContentVar Deref
| ContentUrl Bool Deref
| ContentEmbed Deref
| ContentMsg Deref
| ContentAttrs Deref
deriving (Int -> Content -> ShowS
[Content] -> ShowS
Content -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Content] -> ShowS
$cshowList :: [Content] -> ShowS
show :: Content -> String
$cshow :: Content -> String
showsPrec :: Int -> Content -> ShowS
$cshowsPrec :: Int -> Content -> ShowS
Show, Content -> Content -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Content -> Content -> Bool
$c/= :: Content -> Content -> Bool
== :: Content -> Content -> Bool
$c== :: Content -> Content -> Bool
Eq, ReadPrec [Content]
ReadPrec Content
Int -> ReadS Content
ReadS [Content]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Content]
$creadListPrec :: ReadPrec [Content]
readPrec :: ReadPrec Content
$creadPrec :: ReadPrec Content
readList :: ReadS [Content]
$creadList :: ReadS [Content]
readsPrec :: Int -> ReadS Content
$creadsPrec :: Int -> ReadS Content
Read, Typeable Content
Content -> DataType
Content -> Constr
(forall b. Data b => b -> b) -> Content -> Content
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Content -> u
forall u. (forall d. Data d => d -> u) -> Content -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Content -> m Content
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Content
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Content)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Content -> m Content
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Content -> m Content
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Content -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Content -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Content -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Content -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Content -> r
gmapT :: (forall b. Data b => b -> b) -> Content -> Content
$cgmapT :: (forall b. Data b => b -> b) -> Content -> Content
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Content)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Content)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Content)
dataTypeOf :: Content -> DataType
$cdataTypeOf :: Content -> DataType
toConstr :: Content -> Constr
$ctoConstr :: Content -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Content
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Content
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content
Data, Typeable)
data Line = LineForall Deref Binding
| LineIf Deref
| LineElseIf Deref
| LineElse
| LineWith [(Deref, Binding)]
| LineMaybe Deref Binding
| LineNothing
| LineCase Deref
| LineOf Binding
| LineTag
{ Line -> String
_lineTagName :: String
, Line -> [(Maybe Deref, String, Maybe [Content])]
_lineAttr :: [(Maybe Deref, String, Maybe [Content])]
, Line -> [Content]
_lineContent :: [Content]
, Line -> [(Maybe Deref, [Content])]
_lineClasses :: [(Maybe Deref, [Content])]
, Line -> [Deref]
_lineAttrs :: [Deref]
, Line -> Bool
_lineNoNewline :: Bool
}
| LineContent [Content] Bool
deriving (Line -> Line -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Line -> Line -> Bool
$c/= :: Line -> Line -> Bool
== :: Line -> Line -> Bool
$c== :: Line -> Line -> Bool
Eq, Int -> Line -> ShowS
[Line] -> ShowS
Line -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Line] -> ShowS
$cshowList :: [Line] -> ShowS
show :: Line -> String
$cshow :: Line -> String
showsPrec :: Int -> Line -> ShowS
$cshowsPrec :: Int -> Line -> ShowS
Show, ReadPrec [Line]
ReadPrec Line
Int -> ReadS Line
ReadS [Line]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Line]
$creadListPrec :: ReadPrec [Line]
readPrec :: ReadPrec Line
$creadPrec :: ReadPrec Line
readList :: ReadS [Line]
$creadList :: ReadS [Line]
readsPrec :: Int -> ReadS Line
$creadsPrec :: Int -> ReadS Line
Read)
parseLines :: HamletSettings -> String -> Result (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
parseLines :: HamletSettings
-> String
-> Result (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
parseLines HamletSettings
set String
s =
case forall s t a.
Stream s Identity t =>
Parsec s () a -> String -> s -> Either ParseError a
parse ParsecT
String
()
Identity
(Maybe NewlineStyle, HamletSettings, [(Int, Line)])
parser String
"[Hamlet input]" String
s of
Left ParseError
e -> forall v. String -> Result v
Error forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show ParseError
e
Right (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
x -> forall a. a -> Result a
Ok (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
x
where
parser :: ParsecT
String
()
Identity
(Maybe NewlineStyle, HamletSettings, [(Int, Line)])
parser = do
Maybe NewlineStyle
mnewline <- ParsecT String () Identity (Maybe NewlineStyle)
parseNewline
let set' :: HamletSettings
set' =
case Maybe NewlineStyle
mnewline of
Maybe NewlineStyle
Nothing ->
case HamletSettings -> NewlineStyle
hamletNewlines HamletSettings
set of
NewlineStyle
DefaultNewlineStyle -> HamletSettings
set { hamletNewlines :: NewlineStyle
hamletNewlines = NewlineStyle
AlwaysNewlines }
NewlineStyle
_ -> HamletSettings
set
Just NewlineStyle
n -> HamletSettings
set { hamletNewlines :: NewlineStyle
hamletNewlines = NewlineStyle
n }
[(Int, Line)]
res <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (HamletSettings -> Parser (Int, Line)
parseLine HamletSettings
set')
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe NewlineStyle
mnewline, HamletSettings
set', [(Int, Line)]
res)
parseNewline :: ParsecT String () Identity (Maybe NewlineStyle)
parseNewline =
(forall tok st a. GenParser tok st a -> GenParser tok st a
try (forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall {u}. ParsecT String u Identity ()
eol' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity String
spaceTabs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$newline ") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity (Maybe NewlineStyle)
parseNewline' forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe NewlineStyle
nl -> forall {u}. ParsecT String u Identity ()
eol' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NewlineStyle
nl) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
parseNewline' :: ParsecT String u Identity (Maybe NewlineStyle)
parseNewline' =
(forall tok st a. GenParser tok st a -> GenParser tok st a
try (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"always") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just NewlineStyle
AlwaysNewlines)) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(forall tok st a. GenParser tok st a -> GenParser tok st a
try (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"never") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just NewlineStyle
NoNewlines)) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(forall tok st a. GenParser tok st a -> GenParser tok st a
try (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"text") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just NewlineStyle
NewlinesText))
eol' :: ParsecT String u Identity ()
eol' = (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\n' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"\r\n" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ())
parseLine :: HamletSettings -> Parser (Int, Line)
parseLine :: HamletSettings -> Parser (Int, Line)
parseLine HamletSettings
set = do
Int
ss <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall a b. (a -> b) -> a -> b
$ forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ((forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
' ' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Int
1) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\t' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Tabs are not allowed in Hamlet indentation"))
Line
x <- forall {st}. ParsecT String st Identity Line
doctype forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {st}. ParsecT String st Identity Line
doctypeDollar forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {st}. ParsecT String st Identity Line
comment forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {st}. ParsecT String st Identity Line
ssiInclude forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {st}. ParsecT String st Identity Line
htmlComment forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {st}. ParsecT String st Identity Line
doctypeRaw forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {st}. ParsecT String st Identity Line
backslash forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
controlIf forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
controlElseIf forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(forall tok st a. GenParser tok st a -> GenParser tok st a
try (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$else") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity String
spaceTabs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
eol forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Line
LineElse) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
controlMaybe forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(forall tok st a. GenParser tok st a -> GenParser tok st a
try (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$nothing") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity String
spaceTabs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
eol forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Line
LineNothing) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
controlForall forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
controlWith forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
controlCase forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
controlOf forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {st}. ParsecT String st Identity Line
angle forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
forall {u} {b}. ParsecT String u Identity b
invalidDollar forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(forall {u}. ParsecT String u Identity ()
eol' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> Bool -> Line
LineContent [] Bool
True)) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(do
([Content]
cs, Bool
avoidNewLines) <- forall {u}.
ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
InContent
Bool
isEof <- (forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Content]
cs Bool -> Bool -> Bool
&& Int
ss forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Bool
isEof
then forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"End of Hamlet template"
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [Content]
cs Bool
avoidNewLines)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
ss, Line
x)
where
eol' :: ParsecT String u Identity ()
eol' = (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\n' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"\r\n" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ())
eol :: ParsecT String u Identity ()
eol = forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. ParsecT String u Identity ()
eol'
doctype :: ParsecT String st Identity Line
doctype = do
forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"!!!" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ HamletSettings -> String
hamletDoctype HamletSettings
set forall a. [a] -> [a] -> [a]
++ String
"\n"] Bool
True
doctypeDollar :: ParsecT String st Identity Line
doctypeDollar = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$doctype "
String
name <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
forall {u}. ParsecT String u Identity ()
eol
case forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
name forall a b. (a -> b) -> a -> b
$ HamletSettings -> [(String, String)]
hamletDoctypeNames HamletSettings
set of
Maybe String
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unknown doctype name: " forall a. [a] -> [a] -> [a]
++ String
name
Just String
val -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ String
val forall a. [a] -> [a] -> [a]
++ String
"\n"] Bool
True
doctypeRaw :: ParsecT String st Identity Line
doctypeRaw = do
String
x <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<!"
String
y <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
x, String
y, String
"\n"]] Bool
True
invalidDollar :: ParsecT String u Identity b
invalidDollar = do
Char
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'$'
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Received a command I did not understand. If you wanted a literal $, start the line with a backslash."
comment :: ParsecT String st Identity Line
comment = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$#"
String
_ <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [] Bool
True
ssiInclude :: ParsecT String st Identity Line
ssiInclude = do
String
x <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<!--#"
String
y <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ String
x forall a. [a] -> [a] -> [a]
++ String
y] Bool
False
htmlComment :: ParsecT String st Identity Line
htmlComment = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<!--"
String
_ <- forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar forall a b. (a -> b) -> a -> b
$ forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"-->"
[String]
x <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall {u}. ParsecT String u Identity String
nonComments
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
x] Bool
False
nonComments :: ParsecT String u Identity String
nonComments = (forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n<") forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
Char
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'<'
(do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"!--"
String
_ <- forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar forall a b. (a -> b) -> a -> b
$ forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"-->"
forall (m :: * -> *) a. Monad m => a -> m a
return String
"") forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *) a. Monad m => a -> m a
return String
"<")
backslash :: ParsecT String u Identity Line
backslash = do
Char
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\'
(forall {u}. ParsecT String u Identity ()
eol forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw String
"\n"] Bool
True))
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Content] -> Bool -> Line
LineContent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {u}.
ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
InContent)
controlIf :: ParsecT String () Identity Line
controlIf = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$if"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- forall a. UserParser a Deref
parseDeref
String
_ <- ParsecT String () Identity String
spaceTabs
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Deref -> Line
LineIf Deref
x
controlElseIf :: ParsecT String () Identity Line
controlElseIf = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$elseif"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- forall a. UserParser a Deref
parseDeref
String
_ <- ParsecT String () Identity String
spaceTabs
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Deref -> Line
LineElseIf Deref
x
binding :: ParsecT String () Identity (Deref, Binding)
binding = do
Binding
y <- Parser Binding
identPattern
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
String
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<-"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- forall a. UserParser a Deref
parseDeref
String
_ <- ParsecT String () Identity String
spaceTabs
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref
x,Binding
y)
bindingSep :: ParsecT String () Identity String
bindingSep = forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
',' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity String
spaceTabs
controlMaybe :: ParsecT String () Identity Line
controlMaybe = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$maybe"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
(Deref
x,Binding
y) <- ParsecT String () Identity (Deref, Binding)
binding
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> Line
LineMaybe Deref
x Binding
y
controlForall :: ParsecT String () Identity Line
controlForall = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$forall"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
(Deref
x,Binding
y) <- ParsecT String () Identity (Deref, Binding)
binding
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> Line
LineForall Deref
x Binding
y
controlWith :: ParsecT String () Identity Line
controlWith = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$with"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[[(Deref, Binding)]]
bindings <- (ParsecT String () Identity (Deref, Binding)
binding forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
`sepBy` ParsecT String () Identity String
bindingSep) forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
`endBy` forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [(Deref, Binding)] -> Line
LineWith forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[(Deref, Binding)]]
bindings
controlCase :: ParsecT String () Identity Line
controlCase = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$case"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- forall a. UserParser a Deref
parseDeref
String
_ <- ParsecT String () Identity String
spaceTabs
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Deref -> Line
LineCase Deref
x
controlOf :: ParsecT String () Identity Line
controlOf = do
String
_ <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$of"
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Binding
x <- Parser Binding
identPattern
String
_ <- ParsecT String () Identity String
spaceTabs
forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Binding -> Line
LineOf Binding
x
content :: ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
cr = do
[(Content, Bool)]
x <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall {u}.
ContentRule -> ParsecT String u Identity (Content, Bool)
content' ContentRule
cr
case ContentRule
cr of
ContentRule
InQuotes -> forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"'
ContentRule
NotInQuotes -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
ContentRule
NotInQuotesAttr -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
ContentRule
InContent -> forall {u}. ParsecT String u Identity ()
eol
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> [Content]
cc forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst [(Content, Bool)]
x, forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any forall a b. (a, b) -> b
snd [(Content, Bool)]
x)
where
cc :: [Content] -> [Content]
cc [] = []
cc (ContentRaw String
a:ContentRaw String
b:[Content]
c) = [Content] -> [Content]
cc forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw (String
a forall a. [a] -> [a] -> [a]
++ String
b) forall a. a -> [a] -> [a]
: [Content]
c
cc (Content
a:[Content]
b) = Content
a forall a. a -> [a] -> [a]
: [Content] -> [Content]
cc [Content]
b
content' :: ContentRule -> ParsecT String u Identity (Content, Bool)
content' ContentRule
cr = forall {u}.
ContentRule -> ParsecT String u Identity (Content, Bool)
contentHash ContentRule
cr
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {a}. ParsecT String a Identity (Content, Bool)
contentAt
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {a}. ParsecT String a Identity (Content, Bool)
contentCaret
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {a}. ParsecT String a Identity (Content, Bool)
contentUnder
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {s} {m :: * -> *} {u}.
Stream s m Char =>
ContentRule -> ParsecT s u m (Content, Bool)
contentReg' ContentRule
cr
contentHash :: ContentRule -> ParsecT String a Identity (Content, Bool)
contentHash ContentRule
cr = do
Either String Deref
x <- forall a. UserParser a (Either String Deref)
parseHash
case Either String Deref
x of
Left String
"#" -> case ContentRule
cr of
ContentRule
NotInQuotes -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected hash at end of line, got Id"
ContentRule
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
"#", Bool
False)
Left String
str -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
str, forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str)
Right Deref
deref -> forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> Content
ContentVar Deref
deref, Bool
False)
contentAt :: ParsecT String a Identity (Content, Bool)
contentAt = do
Either String (Deref, Bool)
x <- forall a. UserParser a (Either String (Deref, Bool))
parseAt
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case Either String (Deref, Bool)
x of
Left String
str -> (String -> Content
ContentRaw String
str, forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str)
Right (Deref
s, Bool
y) -> (Bool -> Deref -> Content
ContentUrl Bool
y Deref
s, Bool
False)
contentCaret :: ParsecT String a Identity (Content, Bool)
contentCaret = do
Either String Deref
x <- forall a. UserParser a (Either String Deref)
parseCaret
case Either String Deref
x of
Left String
str -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
str, forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str)
Right Deref
deref -> forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> Content
ContentEmbed Deref
deref, Bool
False)
contentUnder :: ParsecT String a Identity (Content, Bool)
contentUnder = do
Either String Deref
x <- forall a. UserParser a (Either String Deref)
parseUnder
case Either String Deref
x of
Left String
str -> forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
str, forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str)
Right Deref
deref -> forall (m :: * -> *) a. Monad m => a -> m a
return (Deref -> Content
ContentMsg Deref
deref, Bool
False)
contentReg' :: ContentRule -> ParsecT s u m (Content, Bool)
contentReg' ContentRule
x = (forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) Bool
False) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {s} {m :: * -> *} {u}.
Stream s m Char =>
ContentRule -> ParsecT s u m Content
contentReg ContentRule
x
contentReg :: ContentRule -> ParsecT s u m Content
contentReg ContentRule
InContent = (String -> Content
ContentRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"#@^\r\n"
contentReg ContentRule
NotInQuotes = (String -> Content
ContentRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"@^#. \t\n\r>"
contentReg ContentRule
NotInQuotesAttr = (String -> Content
ContentRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"@^ \t\n\r>"
contentReg ContentRule
InQuotes = (String -> Content
ContentRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"#@^\"\n\r"
tagAttribValue :: ContentRule -> ParsecT String u Identity [Content]
tagAttribValue ContentRule
notInQuotes = do
ContentRule
cr <- (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ContentRule
InQuotes) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *) a. Monad m => a -> m a
return ContentRule
notInQuotes
forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {u}.
ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
cr
tagIdent :: ParsecT String u Identity TagPiece
tagIdent = forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'#' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Content] -> TagPiece
TagIdent forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {u}. ContentRule -> ParsecT String u Identity [Content]
tagAttribValue ContentRule
NotInQuotes
tagCond :: ParsecT String u Identity TagPiece
tagCond = do
Deref
d <- forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':') (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':') forall a. UserParser a Deref
parseDeref
forall {u}. Maybe Deref -> ParsecT String u Identity TagPiece
tagClass (forall a. a -> Maybe a
Just Deref
d) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. Maybe Deref -> ParsecT String u Identity TagPiece
tagAttrib (forall a. a -> Maybe a
Just Deref
d)
tagClass :: Maybe Deref -> ParsecT String u Identity TagPiece
tagClass Maybe Deref
x = forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ((Maybe Deref, [Content]) -> TagPiece
TagClass forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((,)Maybe Deref
x)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {u}. ContentRule -> ParsecT String u Identity [Content]
tagAttribValue ContentRule
NotInQuotes
tagAttrib :: Maybe Deref -> ParsecT String u Identity TagPiece
tagAttrib Maybe Deref
cond = do
String
s <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
" \t=\r\n><"
Maybe [Content]
v <- (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'=' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall {u}. ContentRule -> ParsecT String u Identity [Content]
tagAttribValue ContentRule
NotInQuotesAttr) forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ (Maybe Deref, String, Maybe [Content]) -> TagPiece
TagAttrib (Maybe Deref
cond, String
s, Maybe [Content]
v)
tagAttrs :: ParsecT String u Identity TagPiece
tagAttrs = do
Char
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'*'
Deref
d <- forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{') (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}') forall a. UserParser a Deref
parseDeref
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Deref -> TagPiece
TagAttribs Deref
d
tag' :: [TagPiece]
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
tag' = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr TagPiece
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
tag'' (String
"div", [], [], [])
tag'' :: TagPiece
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
tag'' (TagName String
s) (String
_, [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as) = (String
s, [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as)
tag'' (TagIdent [Content]
s) (String
x, [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as) = (String
x, (forall a. Maybe a
Nothing, String
"id", forall a. a -> Maybe a
Just [Content]
s) forall a. a -> [a] -> [a]
: [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as)
tag'' (TagClass (Maybe Deref, [Content])
s) (String
x, [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as) = (String
x, [(Maybe Deref, String, Maybe [Content])]
y, (Maybe Deref, [Content])
s forall a. a -> [a] -> [a]
: [(Maybe Deref, [Content])]
z, [Deref]
as)
tag'' (TagAttrib (Maybe Deref, String, Maybe [Content])
s) (String
x, [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as) = (String
x, (Maybe Deref, String, Maybe [Content])
s forall a. a -> [a] -> [a]
: [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as)
tag'' (TagAttribs Deref
s) (String
x, [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, [Deref]
as) = (String
x, [(Maybe Deref, String, Maybe [Content])]
y, [(Maybe Deref, [Content])]
z, Deref
s forall a. a -> [a] -> [a]
: [Deref]
as)
ident :: Parser Ident
ident :: Parser Ident
ident = do
String
i <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
alphaNum forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'_' forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\'') forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'(' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> GeneralCategory
generalCategory Char
c forall a. Eq a => a -> a -> Bool
== GeneralCategory
OtherPunctuation)) forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')')
forall {u}. ParsecT String u Identity ()
white
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Ident
Ident String
i)
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"identifier"
parens :: ParsecT String u Identity a -> ParsecT String u Identity a
parens = forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'(' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white) (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white)
brackets :: ParsecT String u Identity a -> ParsecT String u Identity a
brackets = forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'[' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white) (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white)
braces :: ParsecT String u Identity a -> ParsecT String u Identity a
braces = forall s (m :: * -> *) t u open close a.
Stream s m t =>
ParsecT s u m open
-> ParsecT s u m close -> ParsecT s u m a -> ParsecT s u m a
between (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white) (forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white)
comma :: ParsecT String u Identity ()
comma = forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
',' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white
atsign :: ParsecT String u Identity ()
atsign = forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'@' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white
equals :: ParsecT String u Identity ()
equals = forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'=' forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white
white :: ParsecT String u Identity ()
white = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
' '
wildDots :: ParsecT String u Identity ()
wildDots = forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
".." forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall {u}. ParsecT String u Identity ()
white
isVariable :: Ident -> Bool
isVariable (Ident (Char
x:String
_)) = Bool -> Bool
not (Char -> Bool
isUpper Char
x)
isVariable (Ident []) = forall a. HasCallStack => String -> a
error String
"isVariable: bad identifier"
isConstructor :: Ident -> Bool
isConstructor (Ident (Char
x:String
_)) = Char -> Bool
isUpper Char
x Bool -> Bool -> Bool
|| Char -> GeneralCategory
generalCategory Char
x forall a. Eq a => a -> a -> Bool
== GeneralCategory
OtherPunctuation
isConstructor (Ident []) = forall a. HasCallStack => String -> a
error String
"isConstructor: bad identifier"
identPattern :: Parser Binding
identPattern :: Parser Binding
identPattern = Bool -> Parser Binding
gcon Bool
True forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Parser Binding
apat
where
apat :: Parser Binding
apat = forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ Parser Binding
varpat
, Bool -> Parser Binding
gcon Bool
False
, forall {u} {a}.
ParsecT String u Identity a -> ParsecT String u Identity a
parens Parser Binding
tuplepat
, forall {u} {a}.
ParsecT String u Identity a -> ParsecT String u Identity a
brackets Parser Binding
listpat
]
varpat :: Parser Binding
varpat = do
Ident
v <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ do Ident
v <- Parser Ident
ident
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Ident -> Bool
isVariable Ident
v)
forall (m :: * -> *) a. Monad m => a -> m a
return Ident
v
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Ident -> Binding
BindVar Ident
v) forall a b. (a -> b) -> a -> b
$ do
forall {u}. ParsecT String u Identity ()
atsign
Binding
b <- Parser Binding
apat
forall (m :: * -> *) a. Monad m => a -> m a
return (Ident -> Binding -> Binding
BindAs Ident
v Binding
b)
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"variable"
gcon :: Bool -> Parser Binding
gcon :: Bool -> Parser Binding
gcon Bool
allowArgs = do
DataConstr
c <- forall tok st a. GenParser tok st a -> GenParser tok st a
try forall a b. (a -> b) -> a -> b
$ do DataConstr
c <- GenParser Char () DataConstr
dataConstr
forall (m :: * -> *) a. Monad m => a -> m a
return DataConstr
c
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice
[ DataConstr -> Parser Binding
record DataConstr
c
, forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DataConstr -> [Binding] -> Binding
BindConstr DataConstr
c) (forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
allowArgs forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many Parser Binding
apat)
, forall (m :: * -> *) a. Monad m => a -> m a
return (DataConstr -> [Binding] -> Binding
BindConstr DataConstr
c [])
]
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"constructor"
dataConstr :: GenParser Char () DataConstr
dataConstr = do
String
p <- ParsecT String () Identity String
dcPiece
[String]
ps <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT String () Identity String
dcPieces
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> [String] -> DataConstr
toDataConstr String
p [String]
ps
dcPiece :: ParsecT String () Identity String
dcPiece = do
x :: Ident
x@(Ident String
y) <- Parser Ident
ident
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Ident -> Bool
isConstructor Ident
x
forall (m :: * -> *) a. Monad m => a -> m a
return String
y
dcPieces :: ParsecT String () Identity String
dcPieces = do
Char
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.'
ParsecT String () Identity String
dcPiece
toDataConstr :: String -> [String] -> DataConstr
toDataConstr String
x [] = Ident -> DataConstr
DCUnqualified forall a b. (a -> b) -> a -> b
$ String -> Ident
Ident String
x
toDataConstr String
x (String
y:[String]
ys) =
([String] -> [String]) -> String -> [String] -> DataConstr
go (String
xforall a. a -> [a] -> [a]
:) String
y [String]
ys
where
go :: ([String] -> [String]) -> String -> [String] -> DataConstr
go [String] -> [String]
front String
next [] = Module -> Ident -> DataConstr
DCQualified ([String] -> Module
Module forall a b. (a -> b) -> a -> b
$ [String] -> [String]
front []) (String -> Ident
Ident String
next)
go [String] -> [String]
front String
next (String
rest:[String]
rests) = ([String] -> [String]) -> String -> [String] -> DataConstr
go ([String] -> [String]
front forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
nextforall a. a -> [a] -> [a]
:)) String
rest [String]
rests
record :: DataConstr -> Parser Binding
record DataConstr
c = forall {u} {a}.
ParsecT String u Identity a -> ParsecT String u Identity a
braces forall a b. (a -> b) -> a -> b
$ do
([(Ident, Binding)]
fields, Bool
wild) <- forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option ([], Bool
False) forall a b. (a -> b) -> a -> b
$ ParsecT String () Identity ([(Ident, Binding)], Bool)
go
forall (m :: * -> *) a. Monad m => a -> m a
return (DataConstr -> [(Ident, Binding)] -> Bool -> Binding
BindRecord DataConstr
c [(Ident, Binding)]
fields Bool
wild)
where
go :: ParsecT String () Identity ([(Ident, Binding)], Bool)
go = (forall {u}. ParsecT String u Identity ()
wildDots forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ([], Bool
True))
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do (Ident, Binding)
x <- ParsecT String () Identity (Ident, Binding)
recordField
([(Ident, Binding)]
xs,Bool
wild) <- forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option ([],Bool
False) (forall {u}. ParsecT String u Identity ()
comma forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity ([(Ident, Binding)], Bool)
go)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Ident, Binding)
xforall a. a -> [a] -> [a]
:[(Ident, Binding)]
xs,Bool
wild))
recordField :: ParsecT String () Identity (Ident, Binding)
recordField = do
Ident
field <- Parser Ident
ident
Binding
p <- forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option (Ident -> Binding
BindVar Ident
field)
(forall {u}. ParsecT String u Identity ()
equals forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser Binding
identPattern)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ident
field,Binding
p)
tuplepat :: Parser Binding
tuplepat = do
[Binding]
xs <- Parser Binding
identPattern forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
`sepBy` forall {u}. ParsecT String u Identity ()
comma
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case [Binding]
xs of
[Binding
x] -> Binding
x
[Binding]
_ -> [Binding] -> Binding
BindTuple [Binding]
xs
listpat :: Parser Binding
listpat = [Binding] -> Binding
BindList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Binding
identPattern forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
`sepBy` forall {u}. ParsecT String u Identity ()
comma
angle :: ParsecT String u Identity Line
angle = do
Char
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'<'
String
name' <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
" \t.#\r\n!>"
let name :: String
name = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
name' then String
"div" else String
name'
[TagPiece]
xs <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall tok st a. GenParser tok st a -> GenParser tok st a
try ((forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t\r\n") forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(forall {u}. ParsecT String u Identity TagPiece
tagIdent forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. ParsecT String u Identity TagPiece
tagCond forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. Maybe Deref -> ParsecT String u Identity TagPiece
tagClass forall a. Maybe a
Nothing forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. ParsecT String u Identity TagPiece
tagAttrs forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. Maybe Deref -> ParsecT String u Identity TagPiece
tagAttrib forall a. Maybe a
Nothing))
String
_ <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t\r\n"
Char
_ <- forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'>'
([Content]
c, Bool
avoidNewLines) <- forall {u}.
ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
InContent
let (String
tn, [(Maybe Deref, String, Maybe [Content])]
attr, [(Maybe Deref, [Content])]
classes, [Deref]
attrsd) = [TagPiece]
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
tag' forall a b. (a -> b) -> a -> b
$ String -> TagPiece
TagName String
name forall a. a -> [a] -> [a]
: [TagPiece]
xs
if Char
'/' forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
tn
then forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"A tag name may not contain a slash. Perhaps you have a closing tag in your HTML."
else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String
-> [(Maybe Deref, String, Maybe [Content])]
-> [Content]
-> [(Maybe Deref, [Content])]
-> [Deref]
-> Bool
-> Line
LineTag String
tn [(Maybe Deref, String, Maybe [Content])]
attr [Content]
c [(Maybe Deref, [Content])]
classes [Deref]
attrsd Bool
avoidNewLines
data TagPiece = TagName String
| TagIdent [Content]
| TagClass (Maybe Deref, [Content])
| TagAttrib (Maybe Deref, String, Maybe [Content])
| TagAttribs Deref
deriving Int -> TagPiece -> ShowS
[TagPiece] -> ShowS
TagPiece -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagPiece] -> ShowS
$cshowList :: [TagPiece] -> ShowS
show :: TagPiece -> String
$cshow :: TagPiece -> String
showsPrec :: Int -> TagPiece -> ShowS
$cshowsPrec :: Int -> TagPiece -> ShowS
Show
data ContentRule = InQuotes | NotInQuotes | NotInQuotesAttr | InContent
data Nest = Nest Line [Nest]
nestLines :: [(Int, Line)] -> [Nest]
nestLines :: [(Int, Line)] -> [Nest]
nestLines [] = []
nestLines ((Int
i, Line
l):[(Int, Line)]
rest) =
let ([(Int, Line)]
deeper, [(Int, Line)]
rest') = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (\(Int
i', Line
_) -> Int
i' forall a. Ord a => a -> a -> Bool
> Int
i) [(Int, Line)]
rest
in Line -> [Nest] -> Nest
Nest Line
l ([(Int, Line)] -> [Nest]
nestLines [(Int, Line)]
deeper) forall a. a -> [a] -> [a]
: [(Int, Line)] -> [Nest]
nestLines [(Int, Line)]
rest'
data Doc = DocForall Deref Binding [Doc]
| DocWith [(Deref, Binding)] [Doc]
| DocCond [(Deref, [Doc])] (Maybe [Doc])
| DocMaybe Deref Binding [Doc] (Maybe [Doc])
| DocCase Deref [(Binding, [Doc])]
| DocContent Content
deriving (Int -> Doc -> ShowS
[Doc] -> ShowS
Doc -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Doc] -> ShowS
$cshowList :: [Doc] -> ShowS
show :: Doc -> String
$cshow :: Doc -> String
showsPrec :: Int -> Doc -> ShowS
$cshowsPrec :: Int -> Doc -> ShowS
Show, Doc -> Doc -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Doc -> Doc -> Bool
$c/= :: Doc -> Doc -> Bool
== :: Doc -> Doc -> Bool
$c== :: Doc -> Doc -> Bool
Eq, ReadPrec [Doc]
ReadPrec Doc
Int -> ReadS Doc
ReadS [Doc]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Doc]
$creadListPrec :: ReadPrec [Doc]
readPrec :: ReadPrec Doc
$creadPrec :: ReadPrec Doc
readList :: ReadS [Doc]
$creadList :: ReadS [Doc]
readsPrec :: Int -> ReadS Doc
$creadsPrec :: Int -> ReadS Doc
Read, Typeable Doc
Doc -> DataType
Doc -> Constr
(forall b. Data b => b -> b) -> Doc -> Doc
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
forall u. (forall d. Data d => d -> u) -> Doc -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Doc -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Doc -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
gmapT :: (forall b. Data b => b -> b) -> Doc -> Doc
$cgmapT :: (forall b. Data b => b -> b) -> Doc -> Doc
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
dataTypeOf :: Doc -> DataType
$cdataTypeOf :: Doc -> DataType
toConstr :: Doc -> Constr
$ctoConstr :: Doc -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
Data, Typeable)
nestToDoc :: HamletSettings -> [Nest] -> Result [Doc]
nestToDoc :: HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
_set [] = forall a. a -> Result a
Ok []
nestToDoc HamletSettings
set (Nest (LineForall Deref
d Binding
i) [Nest]
inside:[Nest]
rest) = do
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
[Doc]
rest' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest
forall a. a -> Result a
Ok forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> [Doc] -> Doc
DocForall Deref
d Binding
i [Doc]
inside' forall a. a -> [a] -> [a]
: [Doc]
rest'
nestToDoc HamletSettings
set (Nest (LineWith [(Deref, Binding)]
dis) [Nest]
inside:[Nest]
rest) = do
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
[Doc]
rest' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest
forall a. a -> Result a
Ok forall a b. (a -> b) -> a -> b
$ [(Deref, Binding)] -> [Doc] -> Doc
DocWith [(Deref, Binding)]
dis [Doc]
inside' forall a. a -> [a] -> [a]
: [Doc]
rest'
nestToDoc HamletSettings
set (Nest (LineIf Deref
d) [Nest]
inside:[Nest]
rest) = do
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
([(Deref, [Doc])]
ifs, Maybe [Doc]
el, [Nest]
rest') <- HamletSettings
-> ([(Deref, [Doc])] -> [(Deref, [Doc])])
-> [Nest]
-> Result ([(Deref, [Doc])], Maybe [Doc], [Nest])
parseConds HamletSettings
set ((:) (Deref
d, [Doc]
inside')) [Nest]
rest
[Doc]
rest'' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest'
forall a. a -> Result a
Ok forall a b. (a -> b) -> a -> b
$ [(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond [(Deref, [Doc])]
ifs Maybe [Doc]
el forall a. a -> [a] -> [a]
: [Doc]
rest''
nestToDoc HamletSettings
set (Nest (LineMaybe Deref
d Binding
i) [Nest]
inside:[Nest]
rest) = do
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
(Maybe [Doc]
nothing, [Nest]
rest') <-
case [Nest]
rest of
Nest Line
LineNothing [Nest]
ninside:[Nest]
x -> do
[Doc]
ninside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
ninside
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just [Doc]
ninside', [Nest]
x)
[Nest]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Maybe a
Nothing, [Nest]
rest)
[Doc]
rest'' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest'
forall a. a -> Result a
Ok forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> [Doc] -> Maybe [Doc] -> Doc
DocMaybe Deref
d Binding
i [Doc]
inside' Maybe [Doc]
nothing forall a. a -> [a] -> [a]
: [Doc]
rest''
nestToDoc HamletSettings
set (Nest (LineCase Deref
d) [Nest]
inside:[Nest]
rest) = do
let getOf :: Nest -> Result (Binding, [Doc])
getOf (Nest (LineOf Binding
x) [Nest]
insideC) = do
[Doc]
insideC' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
insideC
forall a. a -> Result a
Ok (Binding
x, [Doc]
insideC')
getOf Nest
_ = forall v. String -> Result v
Error String
"Inside a $case there may only be $of. Use '$of _' for a wildcard."
[(Binding, [Doc])]
cases <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Nest -> Result (Binding, [Doc])
getOf [Nest]
inside
[Doc]
rest' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest
forall a. a -> Result a
Ok forall a b. (a -> b) -> a -> b
$ Deref -> [(Binding, [Doc])] -> Doc
DocCase Deref
d [(Binding, [Doc])]
cases forall a. a -> [a] -> [a]
: [Doc]
rest'
nestToDoc HamletSettings
set (Nest (LineTag String
tn [(Maybe Deref, String, Maybe [Content])]
attrs [Content]
content [(Maybe Deref, [Content])]
classes [Deref]
attrsD Bool
avoidNewLine) [Nest]
inside:[Nest]
rest) = do
let attrFix :: (a, b, b) -> (a, b, [(Maybe a, b)])
attrFix (a
x, b
y, b
z) = (a
x, b
y, [(forall a. Maybe a
Nothing, b
z)])
let takeClass :: (a, String, Maybe [a]) -> Maybe (a, [a])
takeClass (a
a, String
"class", Maybe [a]
b) = forall a. a -> Maybe a
Just (a
a, forall a. a -> Maybe a -> a
fromMaybe [] Maybe [a]
b)
takeClass (a, String, Maybe [a])
_ = forall a. Maybe a
Nothing
let clazzes :: [(Maybe Deref, [Content])]
clazzes = [(Maybe Deref, [Content])]
classes forall a. [a] -> [a] -> [a]
++ forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe forall {a} {a}. (a, String, Maybe [a]) -> Maybe (a, [a])
takeClass [(Maybe Deref, String, Maybe [Content])]
attrs
let notClass :: (a, String, c) -> Bool
notClass (a
_, String
x, c
_) = String
x forall a. Eq a => a -> a -> Bool
/= String
"class"
let noclass :: [(Maybe Deref, String, Maybe [Content])]
noclass = forall a. (a -> Bool) -> [a] -> [a]
filter forall {a} {c}. (a, String, c) -> Bool
notClass [(Maybe Deref, String, Maybe [Content])]
attrs
let attrs' :: [(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])]
attrs' =
case [(Maybe Deref, [Content])]
clazzes of
[] -> forall a b. (a -> b) -> [a] -> [b]
map forall {a} {b} {b} {a}. (a, b, b) -> (a, b, [(Maybe a, b)])
attrFix [(Maybe Deref, String, Maybe [Content])]
noclass
[(Maybe Deref, [Content])]
_ -> ([(Maybe Deref, [Content])] -> Maybe Deref
testIncludeClazzes [(Maybe Deref, [Content])]
clazzes, String
"class", forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second forall a. a -> Maybe a
Just) [(Maybe Deref, [Content])]
clazzes)
forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall {a} {b} {b} {a}. (a, b, b) -> (a, b, [(Maybe a, b)])
attrFix [(Maybe Deref, String, Maybe [Content])]
noclass
let closeStyle :: CloseStyle
closeStyle =
if Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Content]
content) Bool -> Bool -> Bool
|| Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Nest]
inside)
then CloseStyle
CloseSeparate
else HamletSettings -> String -> CloseStyle
hamletCloseStyle HamletSettings
set String
tn
let end :: Doc
end = case CloseStyle
closeStyle of
CloseStyle
CloseSeparate ->
Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ String
"</" forall a. [a] -> [a] -> [a]
++ String
tn forall a. [a] -> [a] -> [a]
++ String
">"
CloseStyle
_ -> Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
""
seal :: Doc
seal = case CloseStyle
closeStyle of
CloseStyle
CloseInside -> Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
"/>"
CloseStyle
_ -> Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
">"
start :: Doc
start = Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ String
"<" forall a. [a] -> [a] -> [a]
++ String
tn
attrs'' :: [Doc]
attrs'' = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Maybe Deref, String, [(Maybe Deref, Maybe [Content])]) -> [Doc]
attrToContent [(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])]
attrs'
newline' :: Doc
newline' = Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw
forall a b. (a -> b) -> a -> b
$ case HamletSettings -> NewlineStyle
hamletNewlines HamletSettings
set of { NewlineStyle
AlwaysNewlines | Bool -> Bool
not Bool
avoidNewLine -> String
"\n"; NewlineStyle
_ -> String
"" }
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
[Doc]
rest' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest
forall a. a -> Result a
Ok forall a b. (a -> b) -> a -> b
$ Doc
start
forall a. a -> [a] -> [a]
: [Doc]
attrs''
forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map (Content -> Doc
DocContent forall b c a. (b -> c) -> (a -> b) -> a -> c
. Deref -> Content
ContentAttrs) [Deref]
attrsD
forall a. [a] -> [a] -> [a]
++ Doc
seal
forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent [Content]
content
forall a. [a] -> [a] -> [a]
++ [Doc]
inside'
forall a. [a] -> [a] -> [a]
++ Doc
end
forall a. a -> [a] -> [a]
: Doc
newline'
forall a. a -> [a] -> [a]
: [Doc]
rest'
nestToDoc HamletSettings
set (Nest (LineContent [Content]
content Bool
avoidNewLine) [Nest]
inside:[Nest]
rest) = do
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
[Doc]
rest' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest
let newline' :: Doc
newline' = Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw
forall a b. (a -> b) -> a -> b
$ case HamletSettings -> NewlineStyle
hamletNewlines HamletSettings
set of { NewlineStyle
NoNewlines -> String
""; NewlineStyle
_ -> if Bool
nextIsContent Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
avoidNewLine then String
"\n" else String
"" }
nextIsContent :: Bool
nextIsContent =
case ([Nest]
inside, [Nest]
rest) of
([], Nest LineContent{} [Nest]
_:[Nest]
_) -> Bool
True
([], Nest LineTag{} [Nest]
_:[Nest]
_) -> Bool
True
([Nest], [Nest])
_ -> Bool
False
forall a. a -> Result a
Ok forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent [Content]
content forall a. [a] -> [a] -> [a]
++ Doc
newline'forall a. a -> [a] -> [a]
:[Doc]
inside' forall a. [a] -> [a] -> [a]
++ [Doc]
rest'
nestToDoc HamletSettings
_set (Nest (LineElseIf Deref
_) [Nest]
_:[Nest]
_) = forall v. String -> Result v
Error String
"Unexpected elseif"
nestToDoc HamletSettings
_set (Nest Line
LineElse [Nest]
_:[Nest]
_) = forall v. String -> Result v
Error String
"Unexpected else"
nestToDoc HamletSettings
_set (Nest Line
LineNothing [Nest]
_:[Nest]
_) = forall v. String -> Result v
Error String
"Unexpected nothing"
nestToDoc HamletSettings
_set (Nest (LineOf Binding
_) [Nest]
_:[Nest]
_) = forall v. String -> Result v
Error String
"Unexpected 'of' (did you forget a $case?)"
compressDoc :: [Doc] -> [Doc]
compressDoc :: [Doc] -> [Doc]
compressDoc [] = []
compressDoc (DocForall Deref
d Binding
i [Doc]
doc:[Doc]
rest) =
Deref -> Binding -> [Doc] -> Doc
DocForall Deref
d Binding
i ([Doc] -> [Doc]
compressDoc [Doc]
doc) forall a. a -> [a] -> [a]
: [Doc] -> [Doc]
compressDoc [Doc]
rest
compressDoc (DocWith [(Deref, Binding)]
dis [Doc]
doc:[Doc]
rest) =
[(Deref, Binding)] -> [Doc] -> Doc
DocWith [(Deref, Binding)]
dis ([Doc] -> [Doc]
compressDoc [Doc]
doc) forall a. a -> [a] -> [a]
: [Doc] -> [Doc]
compressDoc [Doc]
rest
compressDoc (DocMaybe Deref
d Binding
i [Doc]
doc Maybe [Doc]
mnothing:[Doc]
rest) =
Deref -> Binding -> [Doc] -> Maybe [Doc] -> Doc
DocMaybe Deref
d Binding
i ([Doc] -> [Doc]
compressDoc [Doc]
doc) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Doc] -> [Doc]
compressDoc Maybe [Doc]
mnothing)
forall a. a -> [a] -> [a]
: [Doc] -> [Doc]
compressDoc [Doc]
rest
compressDoc (DocCond [(Deref
a, [Doc]
x)] Maybe [Doc]
Nothing:DocCond [(Deref
b, [Doc]
y)] Maybe [Doc]
Nothing:[Doc]
rest)
| Deref
a forall a. Eq a => a -> a -> Bool
== Deref
b = [Doc] -> [Doc]
compressDoc forall a b. (a -> b) -> a -> b
$ [(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond [(Deref
a, [Doc]
x forall a. [a] -> [a] -> [a]
++ [Doc]
y)] forall a. Maybe a
Nothing forall a. a -> [a] -> [a]
: [Doc]
rest
compressDoc (DocCond [(Deref, [Doc])]
x Maybe [Doc]
y:[Doc]
rest) =
[(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond (forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second [Doc] -> [Doc]
compressDoc) [(Deref, [Doc])]
x) ([Doc] -> [Doc]
compressDoc forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Maybe [Doc]
y)
forall a. a -> [a] -> [a]
: [Doc] -> [Doc]
compressDoc [Doc]
rest
compressDoc (DocCase Deref
d [(Binding, [Doc])]
cs:[Doc]
rest) =
Deref -> [(Binding, [Doc])] -> Doc
DocCase Deref
d (forall a b. (a -> b) -> [a] -> [b]
map (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second [Doc] -> [Doc]
compressDoc) [(Binding, [Doc])]
cs) forall a. a -> [a] -> [a]
: [Doc] -> [Doc]
compressDoc [Doc]
rest
compressDoc (DocContent (ContentRaw String
""):[Doc]
rest) = [Doc] -> [Doc]
compressDoc [Doc]
rest
compressDoc ( DocContent (ContentRaw String
x)
: DocContent (ContentRaw String
y)
: [Doc]
rest
) = [Doc] -> [Doc]
compressDoc forall a b. (a -> b) -> a -> b
$ (Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ String
x forall a. [a] -> [a] -> [a]
++ String
y) forall a. a -> [a] -> [a]
: [Doc]
rest
compressDoc (DocContent Content
x:[Doc]
rest) = Content -> Doc
DocContent Content
x forall a. a -> [a] -> [a]
: [Doc] -> [Doc]
compressDoc [Doc]
rest
parseDoc :: HamletSettings -> String -> Result (Maybe NewlineStyle, [Doc])
parseDoc :: HamletSettings -> String -> Result (Maybe NewlineStyle, [Doc])
parseDoc HamletSettings
set String
s = do
(Maybe NewlineStyle
mnl, HamletSettings
set', [(Int, Line)]
ls) <- HamletSettings
-> String
-> Result (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
parseLines HamletSettings
set String
s
let notEmpty :: (a, Line) -> Bool
notEmpty (a
_, LineContent [] Bool
_) = Bool
False
notEmpty (a, Line)
_ = Bool
True
let ns :: [Nest]
ns = [(Int, Line)] -> [Nest]
nestLines forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall {a}. (a, Line) -> Bool
notEmpty [(Int, Line)]
ls
[Doc]
ds <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set' [Nest]
ns
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe NewlineStyle
mnl, [Doc] -> [Doc]
compressDoc [Doc]
ds)
attrToContent :: (Maybe Deref, String, [(Maybe Deref, Maybe [Content])]) -> [Doc]
attrToContent :: (Maybe Deref, String, [(Maybe Deref, Maybe [Content])]) -> [Doc]
attrToContent (Just Deref
cond, String
k, [(Maybe Deref, Maybe [Content])]
v) =
[[(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond [(Deref
cond, (Maybe Deref, String, [(Maybe Deref, Maybe [Content])]) -> [Doc]
attrToContent (forall a. Maybe a
Nothing, String
k, [(Maybe Deref, Maybe [Content])]
v))] forall a. Maybe a
Nothing]
attrToContent (Maybe Deref
Nothing, String
k, []) = [Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ Char
' ' forall a. a -> [a] -> [a]
: String
k]
attrToContent (Maybe Deref
Nothing, String
k, [(Maybe Deref
Nothing, Maybe [Content]
Nothing)]) = [Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw forall a b. (a -> b) -> a -> b
$ Char
' ' forall a. a -> [a] -> [a]
: String
k]
attrToContent (Maybe Deref
Nothing, String
k, [(Maybe Deref
Nothing, Just [Content]
v)]) =
Content -> Doc
DocContent (String -> Content
ContentRaw (Char
' ' forall a. a -> [a] -> [a]
: String
k forall a. [a] -> [a] -> [a]
++ String
"=\""))
forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent [Content]
v
forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
"\""]
attrToContent (Maybe Deref
Nothing, String
k, [(Maybe Deref, Maybe [Content])]
v) =
Content -> Doc
DocContent (String -> Content
ContentRaw (Char
' ' forall a. a -> [a] -> [a]
: String
k forall a. [a] -> [a] -> [a]
++ String
"=\""))
forall a. a -> [a] -> [a]
: forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Maybe Deref, Maybe [Content]) -> [Doc]
go (forall a. [a] -> [a]
init [(Maybe Deref, Maybe [Content])]
v)
forall a. [a] -> [a] -> [a]
++ (Maybe Deref, Maybe [Content]) -> [Doc]
go' (forall a. [a] -> a
last [(Maybe Deref, Maybe [Content])]
v)
forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
"\""]
where
go :: (Maybe Deref, Maybe [Content]) -> [Doc]
go (Maybe Deref
Nothing, Maybe [Content]
x) = forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent (forall a. a -> Maybe a -> a
fromMaybe [] Maybe [Content]
x) forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
" "]
go (Just Deref
b, Maybe [Content]
x) =
[ [(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond
[(Deref
b, forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent (forall a. a -> Maybe a -> a
fromMaybe [] Maybe [Content]
x) forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
" "])]
forall a. Maybe a
Nothing
]
go' :: (Maybe Deref, Maybe [Content]) -> [Doc]
go' (Maybe Deref
Nothing, Maybe [Content]
x) = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent) Maybe [Content]
x
go' (Just Deref
b, Maybe [Content]
x) =
[ [(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond
[(Deref
b, forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent) Maybe [Content]
x)]
forall a. Maybe a
Nothing
]
data HamletSettings = HamletSettings
{
HamletSettings -> String
hamletDoctype :: String
, HamletSettings -> NewlineStyle
hamletNewlines :: NewlineStyle
, HamletSettings -> String -> CloseStyle
hamletCloseStyle :: String -> CloseStyle
, HamletSettings -> [(String, String)]
hamletDoctypeNames :: [(String, String)]
}
deriving forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => HamletSettings -> m Exp
forall (m :: * -> *).
Quote m =>
HamletSettings -> Code m HamletSettings
liftTyped :: forall (m :: * -> *).
Quote m =>
HamletSettings -> Code m HamletSettings
$cliftTyped :: forall (m :: * -> *).
Quote m =>
HamletSettings -> Code m HamletSettings
lift :: forall (m :: * -> *). Quote m => HamletSettings -> m Exp
$clift :: forall (m :: * -> *). Quote m => HamletSettings -> m Exp
Lift
data NewlineStyle = NoNewlines
| NewlinesText
| AlwaysNewlines
| DefaultNewlineStyle
deriving (Int -> NewlineStyle -> ShowS
[NewlineStyle] -> ShowS
NewlineStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewlineStyle] -> ShowS
$cshowList :: [NewlineStyle] -> ShowS
show :: NewlineStyle -> String
$cshow :: NewlineStyle -> String
showsPrec :: Int -> NewlineStyle -> ShowS
$cshowsPrec :: Int -> NewlineStyle -> ShowS
Show, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => NewlineStyle -> m Exp
forall (m :: * -> *).
Quote m =>
NewlineStyle -> Code m NewlineStyle
liftTyped :: forall (m :: * -> *).
Quote m =>
NewlineStyle -> Code m NewlineStyle
$cliftTyped :: forall (m :: * -> *).
Quote m =>
NewlineStyle -> Code m NewlineStyle
lift :: forall (m :: * -> *). Quote m => NewlineStyle -> m Exp
$clift :: forall (m :: * -> *). Quote m => NewlineStyle -> m Exp
Lift)
instance Lift (String -> CloseStyle) where
lift :: forall (m :: * -> *). Quote m => (String -> CloseStyle) -> m Exp
lift String -> CloseStyle
_ = [|\s -> htmlCloseStyle s|]
#if MIN_VERSION_template_haskell(2,17,0)
liftTyped :: forall (m :: * -> *).
Quote m =>
(String -> CloseStyle) -> Code m (String -> CloseStyle)
liftTyped = forall a (m :: * -> *). Quote m => m Exp -> Code m a
unsafeCodeCoerce forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
lift
#elif MIN_VERSION_template_haskell(2,16,0)
liftTyped = unsafeTExpCoerce . lift
#endif
htmlEmptyTags :: Set String
htmlEmptyTags :: Set String
htmlEmptyTags = forall a. Eq a => [a] -> Set a
Set.fromAscList
[ String
"area"
, String
"base"
, String
"basefont"
, String
"br"
, String
"col"
, String
"embed"
, String
"frame"
, String
"hr"
, String
"img"
, String
"input"
, String
"isindex"
, String
"keygen"
, String
"link"
, String
"meta"
, String
"param"
, String
"source"
, String
"track"
, String
"wbr"
]
defaultHamletSettings :: HamletSettings
defaultHamletSettings :: HamletSettings
defaultHamletSettings = String
-> NewlineStyle
-> (String -> CloseStyle)
-> [(String, String)]
-> HamletSettings
HamletSettings String
"<!DOCTYPE html>" NewlineStyle
DefaultNewlineStyle String -> CloseStyle
htmlCloseStyle [(String, String)]
doctypeNames
xhtmlHamletSettings :: HamletSettings
xhtmlHamletSettings :: HamletSettings
xhtmlHamletSettings =
String
-> NewlineStyle
-> (String -> CloseStyle)
-> [(String, String)]
-> HamletSettings
HamletSettings String
doctype NewlineStyle
DefaultNewlineStyle String -> CloseStyle
xhtmlCloseStyle [(String, String)]
doctypeNames
where
doctype :: String
doctype =
String
"<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\" " forall a. [a] -> [a] -> [a]
++
String
"\"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\">"
htmlCloseStyle :: String -> CloseStyle
htmlCloseStyle :: String -> CloseStyle
htmlCloseStyle String
s =
if forall a. Ord a => a -> Set a -> Bool
Set.member String
s Set String
htmlEmptyTags
then CloseStyle
NoClose
else CloseStyle
CloseSeparate
xhtmlCloseStyle :: String -> CloseStyle
xhtmlCloseStyle :: String -> CloseStyle
xhtmlCloseStyle String
s =
if forall a. Ord a => a -> Set a -> Bool
Set.member String
s Set String
htmlEmptyTags
then CloseStyle
CloseInside
else CloseStyle
CloseSeparate
data CloseStyle = NoClose | CloseInside | CloseSeparate
parseConds :: HamletSettings
-> ([(Deref, [Doc])] -> [(Deref, [Doc])])
-> [Nest]
-> Result ([(Deref, [Doc])], Maybe [Doc], [Nest])
parseConds :: HamletSettings
-> ([(Deref, [Doc])] -> [(Deref, [Doc])])
-> [Nest]
-> Result ([(Deref, [Doc])], Maybe [Doc], [Nest])
parseConds HamletSettings
set [(Deref, [Doc])] -> [(Deref, [Doc])]
front (Nest Line
LineElse [Nest]
inside:[Nest]
rest) = do
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
forall a. a -> Result a
Ok ([(Deref, [Doc])] -> [(Deref, [Doc])]
front [], forall a. a -> Maybe a
Just [Doc]
inside', [Nest]
rest)
parseConds HamletSettings
set [(Deref, [Doc])] -> [(Deref, [Doc])]
front (Nest (LineElseIf Deref
d) [Nest]
inside:[Nest]
rest) = do
[Doc]
inside' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
inside
HamletSettings
-> ([(Deref, [Doc])] -> [(Deref, [Doc])])
-> [Nest]
-> Result ([(Deref, [Doc])], Maybe [Doc], [Nest])
parseConds HamletSettings
set ([(Deref, [Doc])] -> [(Deref, [Doc])]
front forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:) (Deref
d, [Doc]
inside')) [Nest]
rest
parseConds HamletSettings
_ [(Deref, [Doc])] -> [(Deref, [Doc])]
front [Nest]
rest = forall a. a -> Result a
Ok ([(Deref, [Doc])] -> [(Deref, [Doc])]
front [], forall a. Maybe a
Nothing, [Nest]
rest)
doctypeNames :: [(String, String)]
doctypeNames :: [(String, String)]
doctypeNames =
[ (String
"5", String
"<!DOCTYPE html>")
, (String
"html", String
"<!DOCTYPE html>")
, (String
"1.1", String
"<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.1//EN\" \"http://www.w3.org/TR/xhtml11/DTD/xhtml11.dtd\">")
, (String
"strict", String
"<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\" \"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\">")
]
data Binding = BindVar Ident
| BindAs Ident Binding
| BindConstr DataConstr [Binding]
| BindTuple [Binding]
| BindList [Binding]
| BindRecord DataConstr [(Ident, Binding)] Bool
deriving (Binding -> Binding -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Binding -> Binding -> Bool
$c/= :: Binding -> Binding -> Bool
== :: Binding -> Binding -> Bool
$c== :: Binding -> Binding -> Bool
Eq, Int -> Binding -> ShowS
[Binding] -> ShowS
Binding -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Binding] -> ShowS
$cshowList :: [Binding] -> ShowS
show :: Binding -> String
$cshow :: Binding -> String
showsPrec :: Int -> Binding -> ShowS
$cshowsPrec :: Int -> Binding -> ShowS
Show, ReadPrec [Binding]
ReadPrec Binding
Int -> ReadS Binding
ReadS [Binding]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Binding]
$creadListPrec :: ReadPrec [Binding]
readPrec :: ReadPrec Binding
$creadPrec :: ReadPrec Binding
readList :: ReadS [Binding]
$creadList :: ReadS [Binding]
readsPrec :: Int -> ReadS Binding
$creadsPrec :: Int -> ReadS Binding
Read, Typeable Binding
Binding -> DataType
Binding -> Constr
(forall b. Data b => b -> b) -> Binding -> Binding
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Binding -> u
forall u. (forall d. Data d => d -> u) -> Binding -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binding
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding -> c Binding
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binding)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binding)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binding -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binding -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Binding -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Binding -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding -> r
gmapT :: (forall b. Data b => b -> b) -> Binding -> Binding
$cgmapT :: (forall b. Data b => b -> b) -> Binding -> Binding
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binding)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binding)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binding)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Binding)
dataTypeOf :: Binding -> DataType
$cdataTypeOf :: Binding -> DataType
toConstr :: Binding -> Constr
$ctoConstr :: Binding -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binding
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binding
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding -> c Binding
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding -> c Binding
Data, Typeable)
data DataConstr = DCQualified Module Ident
| DCUnqualified Ident
deriving (DataConstr -> DataConstr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataConstr -> DataConstr -> Bool
$c/= :: DataConstr -> DataConstr -> Bool
== :: DataConstr -> DataConstr -> Bool
$c== :: DataConstr -> DataConstr -> Bool
Eq, Int -> DataConstr -> ShowS
[DataConstr] -> ShowS
DataConstr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataConstr] -> ShowS
$cshowList :: [DataConstr] -> ShowS
show :: DataConstr -> String
$cshow :: DataConstr -> String
showsPrec :: Int -> DataConstr -> ShowS
$cshowsPrec :: Int -> DataConstr -> ShowS
Show, ReadPrec [DataConstr]
ReadPrec DataConstr
Int -> ReadS DataConstr
ReadS [DataConstr]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataConstr]
$creadListPrec :: ReadPrec [DataConstr]
readPrec :: ReadPrec DataConstr
$creadPrec :: ReadPrec DataConstr
readList :: ReadS [DataConstr]
$creadList :: ReadS [DataConstr]
readsPrec :: Int -> ReadS DataConstr
$creadsPrec :: Int -> ReadS DataConstr
Read, Typeable DataConstr
DataConstr -> DataType
DataConstr -> Constr
(forall b. Data b => b -> b) -> DataConstr -> DataConstr
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> DataConstr -> u
forall u. (forall d. Data d => d -> u) -> DataConstr -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DataConstr -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DataConstr -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataConstr
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataConstr -> c DataConstr
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataConstr)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataConstr)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DataConstr -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DataConstr -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> DataConstr -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DataConstr -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DataConstr -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> DataConstr -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DataConstr -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> DataConstr -> r
gmapT :: (forall b. Data b => b -> b) -> DataConstr -> DataConstr
$cgmapT :: (forall b. Data b => b -> b) -> DataConstr -> DataConstr
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataConstr)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataConstr)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataConstr)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c DataConstr)
dataTypeOf :: DataConstr -> DataType
$cdataTypeOf :: DataConstr -> DataType
toConstr :: DataConstr -> Constr
$ctoConstr :: DataConstr -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataConstr
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataConstr
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataConstr -> c DataConstr
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataConstr -> c DataConstr
Data, Typeable)
newtype Module = Module [String]
deriving (Module -> Module -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Module -> Module -> Bool
$c/= :: Module -> Module -> Bool
== :: Module -> Module -> Bool
$c== :: Module -> Module -> Bool
Eq, Int -> Module -> ShowS
[Module] -> ShowS
Module -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Module] -> ShowS
$cshowList :: [Module] -> ShowS
show :: Module -> String
$cshow :: Module -> String
showsPrec :: Int -> Module -> ShowS
$cshowsPrec :: Int -> Module -> ShowS
Show, ReadPrec [Module]
ReadPrec Module
Int -> ReadS Module
ReadS [Module]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Module]
$creadListPrec :: ReadPrec [Module]
readPrec :: ReadPrec Module
$creadPrec :: ReadPrec Module
readList :: ReadS [Module]
$creadList :: ReadS [Module]
readsPrec :: Int -> ReadS Module
$creadsPrec :: Int -> ReadS Module
Read, Typeable Module
Module -> DataType
Module -> Constr
(forall b. Data b => b -> b) -> Module -> Module
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Module -> u
forall u. (forall d. Data d => d -> u) -> Module -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Module -> m Module
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Module -> m Module
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Module
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Module -> c Module
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Module)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Module -> m Module
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Module -> m Module
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Module -> m Module
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Module -> m Module
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Module -> m Module
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Module -> m Module
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Module -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Module -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Module -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Module -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r
gmapT :: (forall b. Data b => b -> b) -> Module -> Module
$cgmapT :: (forall b. Data b => b -> b) -> Module -> Module
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Module)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Module)
dataTypeOf :: Module -> DataType
$cdataTypeOf :: Module -> DataType
toConstr :: Module -> Constr
$ctoConstr :: Module -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Module
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Module
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Module -> c Module
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Module -> c Module
Data, Typeable)
spaceTabs :: Parser String
spaceTabs :: ParsecT String () Identity String
spaceTabs = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t"
testIncludeClazzes :: [(Maybe Deref, [Content])] -> Maybe Deref
testIncludeClazzes :: [(Maybe Deref, [Content])] -> Maybe Deref
testIncludeClazzes [(Maybe Deref, [Content])]
cs
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(Maybe Deref, [Content])]
cs = forall a. Maybe a
Nothing
| Bool
otherwise = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Deref -> Deref -> Deref
DerefBranch (Ident -> Deref
DerefIdent Ident
specialOrIdent) forall a b. (a -> b) -> a -> b
$ [Deref] -> Deref
DerefList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe forall a b. (a, b) -> a
fst [(Maybe Deref, [Content])]
cs
specialOrIdent :: Ident
specialOrIdent :: Ident
specialOrIdent = String -> Ident
Ident String
"__or__hamlet__special"