{-# 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
[Result v] -> ShowS
Result v -> String
(Int -> Result v -> ShowS)
-> (Result v -> String) -> ([Result v] -> ShowS) -> Show (Result v)
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
(Result v -> Result v -> Bool)
-> (Result v -> Result v -> Bool) -> Eq (Result v)
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)
Int -> ReadS (Result v)
ReadS [Result v]
(Int -> ReadS (Result v))
-> ReadS [Result v]
-> ReadPrec (Result v)
-> ReadPrec [Result v]
-> Read (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, Typeable (Result v)
DataType
Constr
Typeable (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 (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Result v))
-> (Result v -> Constr)
-> (Result v -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Result v)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Result v)))
-> ((forall b. Data b => b -> b) -> Result v -> Result v)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r)
-> (forall u. (forall d. Data d => d -> u) -> Result v -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Result v -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v))
-> Data (Result v)
Result v -> DataType
Result v -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (Result v))
(forall b. Data b => b -> b) -> Result v -> Result v
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Result v -> c (Result v)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Result v)
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 u. Int -> (forall d. Data d => d -> u) -> Result v -> u
forall u. (forall d. Data d => d -> u) -> Result v -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Result v -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Result v -> m (Result v)
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))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Result v))
$cOk :: Constr
$cError :: Constr
$tResult :: DataType
gmapMo :: (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 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 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 :: 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 d. Data d => d -> u) -> Result v -> [u]
$cgmapQ :: forall v u.
Data v =>
(forall d. Data d => d -> u) -> Result v -> [u]
gmapQr :: (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 :: (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 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 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 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 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)
$cp1Data :: forall v. Data v => Typeable (Result v)
Data, Typeable)
instance Monad Result where
return :: a -> Result a
return = a -> Result a
forall a. a -> Result a
Ok
Error String
s >>= :: Result a -> (a -> Result b) -> Result b
>>= a -> Result b
_ = String -> 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 :: String -> Result a
fail = String -> Result a
forall v. String -> Result v
Error
#endif
instance Functor Result where
fmap :: (a -> b) -> Result a -> Result b
fmap = (a -> b) -> Result a -> Result b
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM
instance Applicative Result where
pure :: a -> Result a
pure = a -> Result a
forall (m :: * -> *) a. Monad m => a -> m a
return
<*> :: Result (a -> b) -> Result a -> Result 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
(Int -> Content -> ShowS)
-> (Content -> String) -> ([Content] -> ShowS) -> Show Content
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
(Content -> Content -> Bool)
-> (Content -> Content -> Bool) -> Eq Content
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]
(Int -> ReadS Content)
-> ReadS [Content]
-> ReadPrec Content
-> ReadPrec [Content]
-> Read 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
DataType
Constr
Typeable Content
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Content)
-> (Content -> Constr)
-> (Content -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Content -> Content)
-> (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 u. (forall d. Data d => d -> u) -> Content -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Content -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Content -> m Content)
-> Data Content
Content -> DataType
Content -> Constr
(forall b. Data b => b -> b) -> Content -> Content
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Content -> c Content
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cContentAttrs :: Constr
$cContentMsg :: Constr
$cContentEmbed :: Constr
$cContentUrl :: Constr
$cContentVar :: Constr
$cContentRaw :: Constr
$tContent :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Content -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Content -> u
gmapQ :: (forall d. Data d => d -> u) -> Content -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Content -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable 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
(Line -> Line -> Bool) -> (Line -> Line -> Bool) -> Eq Line
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
(Int -> Line -> ShowS)
-> (Line -> String) -> ([Line] -> ShowS) -> Show Line
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]
(Int -> ReadS Line)
-> ReadS [Line] -> ReadPrec Line -> ReadPrec [Line] -> Read 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 Parsec
String () (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
-> String
-> String
-> Either
ParseError (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
forall s t a.
Stream s Identity t =>
Parsec s () a -> String -> s -> Either ParseError a
parse Parsec
String () (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
parser String
s String
s of
Left ParseError
e -> String
-> Result (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
forall v. String -> Result v
Error (String
-> Result (Maybe NewlineStyle, HamletSettings, [(Int, Line)]))
-> String
-> Result (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
forall a b. (a -> b) -> a -> b
$ ParseError -> String
forall a. Show a => a -> String
show ParseError
e
Right (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
x -> (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
-> Result (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
forall a. a -> Result a
Ok (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
x
where
parser :: Parsec
String () (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 <- ParsecT String () Identity (Int, Line)
-> ParsecT String () Identity [(Int, Line)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (HamletSettings -> ParsecT String () Identity (Int, Line)
parseLine HamletSettings
set')
(Maybe NewlineStyle, HamletSettings, [(Int, Line)])
-> Parsec
String () (Maybe NewlineStyle, HamletSettings, [(Int, Line)])
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe NewlineStyle
mnewline, HamletSettings
set', [(Int, Line)]
res)
parseNewline :: ParsecT String () Identity (Maybe NewlineStyle)
parseNewline =
(GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (ParsecT String () Identity () -> ParsecT String () Identity [()]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol' ParsecT String () Identity [()]
-> GenParser Char () String -> GenParser Char () String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GenParser Char () String
spaceTabs GenParser Char () String
-> GenParser Char () String -> GenParser Char () String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$newline ") GenParser Char () String
-> ParsecT String () Identity (Maybe NewlineStyle)
-> ParsecT String () Identity (Maybe NewlineStyle)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity (Maybe NewlineStyle)
forall u. ParsecT String u Identity (Maybe NewlineStyle)
parseNewline' ParsecT String () Identity (Maybe NewlineStyle)
-> (Maybe NewlineStyle
-> ParsecT String () Identity (Maybe NewlineStyle))
-> ParsecT String () Identity (Maybe NewlineStyle)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe NewlineStyle
nl -> ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol' ParsecT String () Identity ()
-> ParsecT String () Identity (Maybe NewlineStyle)
-> ParsecT String () Identity (Maybe NewlineStyle)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe NewlineStyle
-> ParsecT String () Identity (Maybe NewlineStyle)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NewlineStyle
nl) ParsecT String () Identity (Maybe NewlineStyle)
-> ParsecT String () Identity (Maybe NewlineStyle)
-> ParsecT String () Identity (Maybe NewlineStyle)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
Maybe NewlineStyle
-> ParsecT String () Identity (Maybe NewlineStyle)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe NewlineStyle
forall a. Maybe a
Nothing
parseNewline' :: ParsecT String u Identity (Maybe NewlineStyle)
parseNewline' =
(GenParser Char u String -> GenParser Char u String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (String -> GenParser Char u String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"always") GenParser Char u String
-> ParsecT String u Identity (Maybe NewlineStyle)
-> ParsecT String u Identity (Maybe NewlineStyle)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe NewlineStyle
-> ParsecT String u Identity (Maybe NewlineStyle)
forall (m :: * -> *) a. Monad m => a -> m a
return (NewlineStyle -> Maybe NewlineStyle
forall a. a -> Maybe a
Just NewlineStyle
AlwaysNewlines)) ParsecT String u Identity (Maybe NewlineStyle)
-> ParsecT String u Identity (Maybe NewlineStyle)
-> ParsecT String u Identity (Maybe NewlineStyle)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(GenParser Char u String -> GenParser Char u String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (String -> GenParser Char u String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"never") GenParser Char u String
-> ParsecT String u Identity (Maybe NewlineStyle)
-> ParsecT String u Identity (Maybe NewlineStyle)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe NewlineStyle
-> ParsecT String u Identity (Maybe NewlineStyle)
forall (m :: * -> *) a. Monad m => a -> m a
return (NewlineStyle -> Maybe NewlineStyle
forall a. a -> Maybe a
Just NewlineStyle
NoNewlines)) ParsecT String u Identity (Maybe NewlineStyle)
-> ParsecT String u Identity (Maybe NewlineStyle)
-> ParsecT String u Identity (Maybe NewlineStyle)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(GenParser Char u String -> GenParser Char u String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (String -> GenParser Char u String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"text") GenParser Char u String
-> ParsecT String u Identity (Maybe NewlineStyle)
-> ParsecT String u Identity (Maybe NewlineStyle)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe NewlineStyle
-> ParsecT String u Identity (Maybe NewlineStyle)
forall (m :: * -> *) a. Monad m => a -> m a
return (NewlineStyle -> Maybe NewlineStyle
forall a. a -> Maybe a
Just NewlineStyle
NewlinesText))
eol' :: ParsecT String u Identity ()
eol' = (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\n' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) ParsecT String u Identity ()
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"\r\n" ParsecT String u Identity String
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
parseLine :: HamletSettings -> Parser (Int, Line)
parseLine :: HamletSettings -> ParsecT String () Identity (Int, Line)
parseLine HamletSettings
set = do
Int
ss <- ([Int] -> Int)
-> ParsecT String () Identity [Int]
-> ParsecT String () Identity Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (ParsecT String () Identity [Int]
-> ParsecT String () Identity Int)
-> ParsecT String () Identity [Int]
-> ParsecT String () Identity Int
forall a b. (a -> b) -> a -> b
$ ParsecT String () Identity Int -> ParsecT String () Identity [Int]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ((Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
' ' ParsecT String () Identity Char
-> ParsecT String () Identity Int -> ParsecT String () Identity Int
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> ParsecT String () Identity Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
1) ParsecT String () Identity Int
-> ParsecT String () Identity Int -> ParsecT String () Identity Int
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\t' ParsecT String () Identity Char
-> ParsecT String () Identity Int -> ParsecT String () Identity Int
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> ParsecT String () Identity Int
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Tabs are not allowed in Hamlet indentation"))
Line
x <- ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
doctype ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
doctypeDollar ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
comment ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
ssiInclude ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
htmlComment ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
doctypeRaw ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
backslash ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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 ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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 ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$else") GenParser Char () String
-> GenParser Char () String -> GenParser Char () String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GenParser Char () String
spaceTabs GenParser Char () String
-> ParsecT String () Identity () -> ParsecT String () Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol ParsecT String () Identity ()
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return Line
LineElse) ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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 ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$nothing") GenParser Char () String
-> GenParser Char () String -> GenParser Char () String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GenParser Char () String
spaceTabs GenParser Char () String
-> ParsecT String () Identity () -> ParsecT String () Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol ParsecT String () Identity ()
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return Line
LineNothing) ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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 ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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 ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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 ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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 ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall st. ParsecT String st Identity Line
angle ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
ParsecT String () Identity Line
forall u b. ParsecT String u Identity b
invalidDollar ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol' ParsecT String () Identity ()
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> Bool -> Line
LineContent [] Bool
True)) ParsecT String () Identity Line
-> ParsecT String () Identity Line
-> ParsecT String () Identity Line
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) <- ContentRule -> ParsecT String () Identity ([Content], Bool)
forall u.
ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
InContent
Bool
isEof <- (ParsecT String () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT String () Identity ()
-> ParsecT String () Identity Bool
-> ParsecT String () Identity Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> ParsecT String () Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True) ParsecT String () Identity Bool
-> ParsecT String () Identity Bool
-> ParsecT String () Identity Bool
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Bool -> ParsecT String () Identity Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
if [Content] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Content]
cs Bool -> Bool -> Bool
&& Int
ss Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Bool
isEof
then String -> ParsecT String () Identity Line
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"End of Hamlet template"
else Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [Content]
cs Bool
avoidNewLines)
(Int, Line) -> ParsecT String () Identity (Int, Line)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
ss, Line
x)
where
eol' :: ParsecT String u Identity ()
eol' = (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\n' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) ParsecT String u Identity ()
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"\r\n" ParsecT String u Identity String
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
eol :: ParsecT String u Identity ()
eol = ParsecT String u Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT String u Identity ()
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
eol'
doctype :: ParsecT String st Identity Line
doctype = do
GenParser Char st () -> GenParser Char st ()
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st () -> GenParser Char st ())
-> GenParser Char st () -> GenParser Char st ()
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"!!!" ParsecT String st Identity String
-> GenParser Char st () -> GenParser Char st ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GenParser Char st ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String st Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String st Identity Line)
-> Line -> ParsecT String st Identity Line
forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ HamletSettings -> String
hamletDoctype HamletSettings
set String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n"] Bool
True
doctypeDollar :: ParsecT String st Identity Line
doctypeDollar = do
String
_ <- GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char st String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$doctype "
String
name <- ParsecT String st Identity Char -> GenParser Char st String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String st Identity Char -> GenParser Char st String)
-> ParsecT String st Identity Char -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
eol
case String -> [(String, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
name ([(String, String)] -> Maybe String)
-> [(String, String)] -> Maybe String
forall a b. (a -> b) -> a -> b
$ HamletSettings -> [(String, String)]
hamletDoctypeNames HamletSettings
set of
Maybe String
Nothing -> String -> ParsecT String st Identity Line
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> ParsecT String st Identity Line)
-> String -> ParsecT String st Identity Line
forall a b. (a -> b) -> a -> b
$ String
"Unknown doctype name: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name
Just String
val -> Line -> ParsecT String st Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String st Identity Line)
-> Line -> ParsecT String st Identity Line
forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ String
val String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n"] Bool
True
doctypeRaw :: ParsecT String st Identity Line
doctypeRaw = do
String
x <- GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char st String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<!"
String
y <- ParsecT String st Identity Char -> GenParser Char st String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String st Identity Char -> GenParser Char st String)
-> ParsecT String st Identity Char -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String st Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String st Identity Line)
-> Line -> ParsecT String st Identity Line
forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ [String] -> String
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
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'$'
String -> ParsecT String u Identity b
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
_ <- GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char st String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$#"
String
_ <- ParsecT String st Identity Char -> GenParser Char st String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String st Identity Char -> GenParser Char st String)
-> ParsecT String st Identity Char -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String st Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String st Identity Line)
-> Line -> ParsecT String st Identity Line
forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [] Bool
True
ssiInclude :: ParsecT String st Identity Line
ssiInclude = do
String
x <- GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char st String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<!--#"
String
y <- ParsecT String st Identity Char -> GenParser Char st String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String st Identity Char -> GenParser Char st String)
-> ParsecT String st Identity Char -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String st Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n"
ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String st Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String st Identity Line)
-> Line -> ParsecT String st Identity Line
forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ String
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
y] Bool
False
htmlComment :: ParsecT String st Identity Line
htmlComment = do
String
_ <- GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char st String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<!--"
String
_ <- ParsecT String st Identity Char
-> GenParser Char st String -> GenParser Char st 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 ParsecT String st Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ GenParser Char st String -> GenParser Char st String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char st String -> GenParser Char st String)
-> GenParser Char st String -> GenParser Char st String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char st String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"-->"
[String]
x <- GenParser Char st String -> ParsecT String st Identity [String]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many GenParser Char st String
forall u. ParsecT String u Identity String
nonComments
ParsecT String st Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String st Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String st Identity Line)
-> Line -> ParsecT String st Identity Line
forall a b. (a -> b) -> a -> b
$ [Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
x] Bool
False
nonComments :: ParsecT String u Identity String
nonComments = (ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT String u Identity Char
-> ParsecT String u Identity String)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"\r\n<") ParsecT String u Identity String
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (do
Char
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'<'
(do
String
_ <- ParsecT String u Identity String
-> ParsecT String u Identity String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (ParsecT String u Identity String
-> ParsecT String u Identity String)
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"!--"
String
_ <- ParsecT String u Identity Char
-> ParsecT String u Identity String
-> ParsecT String u Identity 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 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
anyChar (ParsecT String u Identity String
-> ParsecT String u Identity String)
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ ParsecT String u Identity String
-> ParsecT String u Identity String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (ParsecT String u Identity String
-> ParsecT String u Identity String)
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"-->"
String -> ParsecT String u Identity String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"") ParsecT String u Identity String
-> ParsecT String u Identity String
-> ParsecT String u Identity String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> String -> ParsecT String u Identity String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"<")
backslash :: ParsecT String u Identity Line
backslash = do
Char
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\'
(ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
eol ParsecT String u Identity ()
-> ParsecT String u Identity Line -> ParsecT String u Identity Line
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Line -> ParsecT String u Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> Bool -> Line
LineContent [String -> Content
ContentRaw String
"\n"] Bool
True))
ParsecT String u Identity Line
-> ParsecT String u Identity Line -> ParsecT String u Identity Line
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (([Content] -> Bool -> Line) -> ([Content], Bool) -> Line
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Content] -> Bool -> Line
LineContent (([Content], Bool) -> Line)
-> ParsecT String u Identity ([Content], Bool)
-> ParsecT String u Identity Line
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ContentRule -> ParsecT String u Identity ([Content], Bool)
forall u.
ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
InContent)
controlIf :: ParsecT String () Identity Line
controlIf = do
String
_ <- GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () String -> GenParser Char () String)
-> GenParser Char () String -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$if"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- UserParser () Deref
forall a. UserParser a Deref
parseDeref
String
_ <- GenParser Char () String
spaceTabs
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
forall a b. (a -> b) -> a -> b
$ Deref -> Line
LineIf Deref
x
controlElseIf :: ParsecT String () Identity Line
controlElseIf = do
String
_ <- GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () String -> GenParser Char () String)
-> GenParser Char () String -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$elseif"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- UserParser () Deref
forall a. UserParser a Deref
parseDeref
String
_ <- GenParser Char () String
spaceTabs
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
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
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
String
_ <- String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"<-"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- UserParser () Deref
forall a. UserParser a Deref
parseDeref
String
_ <- GenParser Char () String
spaceTabs
(Deref, Binding) -> ParsecT String () Identity (Deref, Binding)
forall (m :: * -> *) a. Monad m => a -> m a
return (Deref
x,Binding
y)
bindingSep :: GenParser Char () String
bindingSep = Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
',' ParsecT String () Identity Char
-> GenParser Char () String -> GenParser Char () String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> GenParser Char () String
spaceTabs
controlMaybe :: ParsecT String () Identity Line
controlMaybe = do
String
_ <- GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () String -> GenParser Char () String)
-> GenParser Char () String -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$maybe"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
(Deref
x,Binding
y) <- ParsecT String () Identity (Deref, Binding)
binding
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> Line
LineMaybe Deref
x Binding
y
controlForall :: ParsecT String () Identity Line
controlForall = do
String
_ <- GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () String -> GenParser Char () String)
-> GenParser Char () String -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$forall"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
(Deref
x,Binding
y) <- ParsecT String () Identity (Deref, Binding)
binding
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> Line
LineForall Deref
x Binding
y
controlWith :: ParsecT String () Identity Line
controlWith = do
String
_ <- GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () String -> GenParser Char () String)
-> GenParser Char () String -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$with"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
[[(Deref, Binding)]]
bindings <- (ParsecT String () Identity (Deref, Binding)
binding ParsecT String () Identity (Deref, Binding)
-> GenParser Char () String
-> ParsecT String () Identity [(Deref, 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` GenParser Char () String
bindingSep) ParsecT String () Identity [(Deref, Binding)]
-> ParsecT String () Identity ()
-> ParsecT String () Identity [[(Deref, 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]
`endBy` ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
forall a b. (a -> b) -> a -> b
$ [(Deref, Binding)] -> Line
LineWith ([(Deref, Binding)] -> Line) -> [(Deref, Binding)] -> Line
forall a b. (a -> b) -> a -> b
$ [[(Deref, Binding)]] -> [(Deref, Binding)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[(Deref, Binding)]]
bindings
controlCase :: ParsecT String () Identity Line
controlCase = do
String
_ <- GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () String -> GenParser Char () String)
-> GenParser Char () String -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$case"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Deref
x <- UserParser () Deref
forall a. UserParser a Deref
parseDeref
String
_ <- GenParser Char () String
spaceTabs
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
forall a b. (a -> b) -> a -> b
$ Deref -> Line
LineCase Deref
x
controlOf :: ParsecT String () Identity Line
controlOf = do
String
_ <- GenParser Char () String -> GenParser Char () String
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () String -> GenParser Char () String)
-> GenParser Char () String -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> GenParser Char () String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
"$of"
ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
spaces
Binding
x <- Parser Binding
identPattern
String
_ <- GenParser Char () String
spaceTabs
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
eol
Line -> ParsecT String () Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String () Identity Line)
-> Line -> ParsecT String () Identity Line
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 <- ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity [(Content, Bool)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity [(Content, Bool)])
-> ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity [(Content, Bool)]
forall a b. (a -> b) -> a -> b
$ ContentRule -> ParsecT String u Identity (Content, Bool)
forall u. ContentRule -> ParsecT String u Identity (Content, Bool)
content' ContentRule
cr
case ContentRule
cr of
ContentRule
InQuotes -> ParsecT String u Identity Char -> ParsecT String u Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT String u Identity Char -> ParsecT String u Identity ())
-> ParsecT String u Identity Char -> ParsecT String u Identity ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"'
ContentRule
NotInQuotes -> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
ContentRule
NotInQuotesAttr -> () -> ParsecT String u Identity ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
ContentRule
InContent -> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
eol
([Content], Bool) -> ParsecT String u Identity ([Content], Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Content] -> [Content]
cc ([Content] -> [Content]) -> [Content] -> [Content]
forall a b. (a -> b) -> a -> b
$ ((Content, Bool) -> Content) -> [(Content, Bool)] -> [Content]
forall a b. (a -> b) -> [a] -> [b]
map (Content, Bool) -> Content
forall a b. (a, b) -> a
fst [(Content, Bool)]
x, ((Content, Bool) -> Bool) -> [(Content, Bool)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Content, Bool) -> Bool
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 ([Content] -> [Content]) -> [Content] -> [Content]
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw (String
a String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
b) Content -> [Content] -> [Content]
forall a. a -> [a] -> [a]
: [Content]
c
cc (Content
a:[Content]
b) = Content
a Content -> [Content] -> [Content]
forall a. a -> [a] -> [a]
: [Content] -> [Content]
cc [Content]
b
content' :: ContentRule -> ParsecT String u Identity (Content, Bool)
content' ContentRule
cr = ContentRule -> ParsecT String u Identity (Content, Bool)
forall u. ContentRule -> ParsecT String u Identity (Content, Bool)
contentHash ContentRule
cr
ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity (Content, Bool)
forall a. ParsecT String a Identity (Content, Bool)
contentAt
ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity (Content, Bool)
forall a. ParsecT String a Identity (Content, Bool)
contentCaret
ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity (Content, Bool)
forall a. ParsecT String a Identity (Content, Bool)
contentUnder
ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
-> ParsecT String u Identity (Content, Bool)
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ContentRule -> ParsecT String u Identity (Content, Bool)
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 <- UserParser a (Either String Deref)
forall a. UserParser a (Either String Deref)
parseHash
case Either String Deref
x of
Left String
"#" -> case ContentRule
cr of
ContentRule
NotInQuotes -> String -> ParsecT String a Identity (Content, Bool)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected hash at end of line, got Id"
ContentRule
_ -> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
"#", Bool
False)
Left String
str -> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
str, String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str)
Right Deref
deref -> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
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 <- UserParser a (Either String (Deref, Bool))
forall a. UserParser a (Either String (Deref, Bool))
parseAt
(Content, Bool) -> ParsecT String a Identity (Content, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Content, Bool) -> ParsecT String a Identity (Content, Bool))
-> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
forall a b. (a -> b) -> a -> b
$ case Either String (Deref, Bool)
x of
Left String
str -> (String -> Content
ContentRaw String
str, String -> Bool
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 <- UserParser a (Either String Deref)
forall a. UserParser a (Either String Deref)
parseCaret
case Either String Deref
x of
Left String
str -> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
str, String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str)
Right Deref
deref -> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
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 <- UserParser a (Either String Deref)
forall a. UserParser a (Either String Deref)
parseUnder
case Either String Deref
x of
Left String
str -> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Content
ContentRaw String
str, String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
str)
Right Deref
deref -> (Content, Bool) -> ParsecT String a Identity (Content, Bool)
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 = ((Content -> Bool -> (Content, Bool))
-> Bool -> Content -> (Content, Bool)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) Bool
False) (Content -> (Content, Bool))
-> ParsecT s u m Content -> ParsecT s u m (Content, Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ContentRule -> ParsecT s u m Content
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 (String -> Content) -> (Char -> String) -> Char -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall (m :: * -> *) a. Monad m => a -> m a
return) (Char -> Content) -> ParsecT s u m Char -> ParsecT s u m Content
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ParsecT s u m Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
"#@^\r\n"
contentReg ContentRule
NotInQuotes = (String -> Content
ContentRaw (String -> Content) -> (Char -> String) -> Char -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall (m :: * -> *) a. Monad m => a -> m a
return) (Char -> Content) -> ParsecT s u m Char -> ParsecT s u m Content
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ParsecT s u m Char
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 (String -> Content) -> (Char -> String) -> Char -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall (m :: * -> *) a. Monad m => a -> m a
return) (Char -> Content) -> ParsecT s u m Char -> ParsecT s u m Content
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ParsecT s u m Char
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 (String -> Content) -> (Char -> String) -> Char -> Content
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> String
forall (m :: * -> *) a. Monad m => a -> m a
return) (Char -> Content) -> ParsecT s u m Char -> ParsecT s u m Content
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> ParsecT s u m Char
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 <- (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'"' ParsecT String u Identity Char
-> ParsecT String u Identity ContentRule
-> ParsecT String u Identity ContentRule
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ContentRule -> ParsecT String u Identity ContentRule
forall (m :: * -> *) a. Monad m => a -> m a
return ContentRule
InQuotes) ParsecT String u Identity ContentRule
-> ParsecT String u Identity ContentRule
-> ParsecT String u Identity ContentRule
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ContentRule -> ParsecT String u Identity ContentRule
forall (m :: * -> *) a. Monad m => a -> m a
return ContentRule
notInQuotes
([Content], Bool) -> [Content]
forall a b. (a, b) -> a
fst (([Content], Bool) -> [Content])
-> ParsecT String u Identity ([Content], Bool)
-> ParsecT String u Identity [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ContentRule -> ParsecT String u Identity ([Content], Bool)
forall u.
ContentRule -> ParsecT String u Identity ([Content], Bool)
content ContentRule
cr
tagIdent :: ParsecT String u Identity TagPiece
tagIdent = Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'#' ParsecT String u Identity Char
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Content] -> TagPiece
TagIdent ([Content] -> TagPiece)
-> ParsecT String u Identity [Content]
-> ParsecT String u Identity TagPiece
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ContentRule -> ParsecT String u Identity [Content]
forall u. ContentRule -> ParsecT String u Identity [Content]
tagAttribValue ContentRule
NotInQuotes
tagCond :: ParsecT String u Identity TagPiece
tagCond = do
Deref
d <- ParsecT String u Identity Char
-> ParsecT String u Identity Char
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
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 (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':') (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
':') ParsecT String u Identity Deref
forall a. UserParser a Deref
parseDeref
Maybe Deref -> ParsecT String u Identity TagPiece
forall u. Maybe Deref -> ParsecT String u Identity TagPiece
tagClass (Deref -> Maybe Deref
forall a. a -> Maybe a
Just Deref
d) ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Deref -> ParsecT String u Identity TagPiece
forall u. Maybe Deref -> ParsecT String u Identity TagPiece
tagAttrib (Deref -> Maybe Deref
forall a. a -> Maybe a
Just Deref
d)
tagClass :: Maybe Deref -> ParsecT String u Identity TagPiece
tagClass Maybe Deref
x = Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.' ParsecT String u Identity Char
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ((Maybe Deref, [Content]) -> TagPiece
TagClass ((Maybe Deref, [Content]) -> TagPiece)
-> ([Content] -> (Maybe Deref, [Content])) -> [Content] -> TagPiece
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((,)Maybe Deref
x)) ([Content] -> TagPiece)
-> ParsecT String u Identity [Content]
-> ParsecT String u Identity TagPiece
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ContentRule -> ParsecT String u Identity [Content]
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 <- ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT String u Identity Char
-> ParsecT String u Identity String)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
" \t=\r\n><"
Maybe [Content]
v <- (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'=' ParsecT String u Identity Char
-> ParsecT String u Identity (Maybe [Content])
-> ParsecT String u Identity (Maybe [Content])
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Content] -> Maybe [Content]
forall a. a -> Maybe a
Just ([Content] -> Maybe [Content])
-> ParsecT String u Identity [Content]
-> ParsecT String u Identity (Maybe [Content])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ContentRule -> ParsecT String u Identity [Content]
forall u. ContentRule -> ParsecT String u Identity [Content]
tagAttribValue ContentRule
NotInQuotesAttr) ParsecT String u Identity (Maybe [Content])
-> ParsecT String u Identity (Maybe [Content])
-> ParsecT String u Identity (Maybe [Content])
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe [Content] -> ParsecT String u Identity (Maybe [Content])
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Content]
forall a. Maybe a
Nothing
TagPiece -> ParsecT String u Identity TagPiece
forall (m :: * -> *) a. Monad m => a -> m a
return (TagPiece -> ParsecT String u Identity TagPiece)
-> TagPiece -> ParsecT String u Identity TagPiece
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
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'*'
Deref
d <- ParsecT String u Identity Char
-> ParsecT String u Identity Char
-> ParsecT String u Identity Deref
-> ParsecT String u Identity Deref
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 (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{') (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}') ParsecT String u Identity Deref
forall a. UserParser a Deref
parseDeref
TagPiece -> ParsecT String u Identity TagPiece
forall (m :: * -> *) a. Monad m => a -> m a
return (TagPiece -> ParsecT String u Identity TagPiece)
-> TagPiece -> ParsecT String u Identity TagPiece
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' = (TagPiece
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref]))
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
-> [TagPiece]
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
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, (Maybe Deref
forall a. Maybe a
Nothing, String
"id", [Content] -> Maybe [Content]
forall a. a -> Maybe a
Just [Content]
s) (Maybe Deref, String, Maybe [Content])
-> [(Maybe Deref, String, Maybe [Content])]
-> [(Maybe Deref, String, Maybe [Content])]
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 (Maybe Deref, [Content])
-> [(Maybe Deref, [Content])] -> [(Maybe Deref, [Content])]
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 (Maybe Deref, String, Maybe [Content])
-> [(Maybe Deref, String, Maybe [Content])]
-> [(Maybe Deref, String, Maybe [Content])]
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 Deref -> [Deref] -> [Deref]
forall a. a -> [a] -> [a]
: [Deref]
as)
ident :: Parser Ident
ident :: Parser Ident
ident = do
String
i <- ParsecT String () Identity Char -> GenParser Char () String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
alphaNum ParsecT String () Identity Char
-> ParsecT String () Identity Char
-> ParsecT String () Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'_' ParsecT String () Identity Char
-> ParsecT String () Identity Char
-> ParsecT String () Identity Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\'') GenParser Char () String
-> GenParser Char () String -> GenParser Char () String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|>
(Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'(' ParsecT String () Identity Char
-> GenParser Char () String -> GenParser Char () String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT String () Identity Char -> GenParser Char () String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ((Char -> Bool) -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> GeneralCategory
generalCategory Char
c GeneralCategory -> GeneralCategory -> Bool
forall a. Eq a => a -> a -> Bool
== GeneralCategory
OtherPunctuation)) GenParser Char () String
-> ParsecT String () Identity Char -> GenParser Char () String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')')
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
white
Ident -> Parser Ident
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Ident
Ident String
i)
Parser Ident -> String -> Parser Ident
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 = ParsecT String u Identity ()
-> ParsecT String u Identity ()
-> ParsecT String u Identity a
-> ParsecT String u Identity a
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 (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'(' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white) (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
')' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white)
brackets :: ParsecT String u Identity a -> ParsecT String u Identity a
brackets = ParsecT String u Identity ()
-> ParsecT String u Identity ()
-> ParsecT String u Identity a
-> ParsecT String u Identity a
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 (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'[' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white) (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
']' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white)
braces :: ParsecT String u Identity a -> ParsecT String u Identity a
braces = ParsecT String u Identity ()
-> ParsecT String u Identity ()
-> ParsecT String u Identity a
-> ParsecT String u Identity a
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 (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'{' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white) (Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'}' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white)
comma :: ParsecT String u Identity ()
comma = Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
',' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white
atsign :: ParsecT String u Identity ()
atsign = Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'@' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white
equals :: ParsecT String u Identity ()
equals = Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'=' ParsecT String u Identity Char
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
forall u. ParsecT String u Identity ()
white
white :: ParsecT String u Identity ()
white = ParsecT String u Identity Char -> ParsecT String u Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany (ParsecT String u Identity Char -> ParsecT String u Identity ())
-> ParsecT String u Identity Char -> ParsecT String u Identity ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
' '
wildDots :: ParsecT String u Identity ()
wildDots = String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
string String
".." ParsecT String u Identity String
-> ParsecT String u Identity () -> ParsecT String u Identity ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String u Identity ()
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 []) = String -> Bool
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 GeneralCategory -> GeneralCategory -> Bool
forall a. Eq a => a -> a -> Bool
== GeneralCategory
OtherPunctuation
isConstructor (Ident []) = String -> Bool
forall a. HasCallStack => String -> a
error String
"isConstructor: bad identifier"
identPattern :: Parser Binding
identPattern :: Parser Binding
identPattern = Bool -> Parser Binding
gcon Bool
True Parser Binding -> Parser Binding -> Parser Binding
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 = [Parser Binding] -> Parser Binding
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
, Parser Binding -> Parser Binding
forall u a.
ParsecT String u Identity a -> ParsecT String u Identity a
parens Parser Binding
tuplepat
, Parser Binding -> Parser Binding
forall u a.
ParsecT String u Identity a -> ParsecT String u Identity a
brackets Parser Binding
listpat
]
varpat :: Parser Binding
varpat = do
Ident
v <- Parser Ident -> Parser Ident
forall tok st a. GenParser tok st a -> GenParser tok st a
try (Parser Ident -> Parser Ident) -> Parser Ident -> Parser Ident
forall a b. (a -> b) -> a -> b
$ do Ident
v <- Parser Ident
ident
Bool -> ParsecT String () Identity ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Ident -> Bool
isVariable Ident
v)
Ident -> Parser Ident
forall (m :: * -> *) a. Monad m => a -> m a
return Ident
v
Binding -> Parser Binding -> Parser Binding
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) (Parser Binding -> Parser Binding)
-> Parser Binding -> Parser Binding
forall a b. (a -> b) -> a -> b
$ do
ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
atsign
Binding
b <- Parser Binding
apat
Binding -> Parser Binding
forall (m :: * -> *) a. Monad m => a -> m a
return (Ident -> Binding -> Binding
BindAs Ident
v Binding
b)
Parser Binding -> String -> Parser Binding
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 <- GenParser Char () DataConstr -> GenParser Char () DataConstr
forall tok st a. GenParser tok st a -> GenParser tok st a
try (GenParser Char () DataConstr -> GenParser Char () DataConstr)
-> GenParser Char () DataConstr -> GenParser Char () DataConstr
forall a b. (a -> b) -> a -> b
$ do DataConstr
c <- GenParser Char () DataConstr
dataConstr
DataConstr -> GenParser Char () DataConstr
forall (m :: * -> *) a. Monad m => a -> m a
return DataConstr
c
[Parser Binding] -> Parser Binding
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
, ([Binding] -> Binding)
-> ParsecT String () Identity [Binding] -> Parser Binding
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (DataConstr -> [Binding] -> Binding
BindConstr DataConstr
c) (Bool -> ParsecT String () Identity ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard Bool
allowArgs ParsecT String () Identity ()
-> ParsecT String () Identity [Binding]
-> ParsecT String () Identity [Binding]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser Binding -> ParsecT String () Identity [Binding]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many Parser Binding
apat)
, Binding -> Parser Binding
forall (m :: * -> *) a. Monad m => a -> m a
return (DataConstr -> [Binding] -> Binding
BindConstr DataConstr
c [])
]
Parser Binding -> String -> Parser Binding
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 <- GenParser Char () String
dcPiece
[String]
ps <- GenParser Char () String -> ParsecT String () Identity [String]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many GenParser Char () String
dcPieces
DataConstr -> GenParser Char () DataConstr
forall (m :: * -> *) a. Monad m => a -> m a
return (DataConstr -> GenParser Char () DataConstr)
-> DataConstr -> GenParser Char () DataConstr
forall a b. (a -> b) -> a -> b
$ String -> [String] -> DataConstr
toDataConstr String
p [String]
ps
dcPiece :: GenParser Char () String
dcPiece = do
x :: Ident
x@(Ident String
y) <- Parser Ident
ident
Bool -> ParsecT String () Identity ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT String () Identity ())
-> Bool -> ParsecT String () Identity ()
forall a b. (a -> b) -> a -> b
$ Ident -> Bool
isConstructor Ident
x
String -> GenParser Char () String
forall (m :: * -> *) a. Monad m => a -> m a
return String
y
dcPieces :: GenParser Char () String
dcPieces = do
Char
_ <- Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'.'
GenParser Char () String
dcPiece
toDataConstr :: String -> [String] -> DataConstr
toDataConstr String
x [] = Ident -> DataConstr
DCUnqualified (Ident -> DataConstr) -> Ident -> DataConstr
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
xString -> [String] -> [String]
forall 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 ([String] -> Module) -> [String] -> 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 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
nextString -> [String] -> [String]
forall a. a -> [a] -> [a]
:)) String
rest [String]
rests
record :: DataConstr -> Parser Binding
record DataConstr
c = Parser Binding -> Parser Binding
forall u a.
ParsecT String u Identity a -> ParsecT String u Identity a
braces (Parser Binding -> Parser Binding)
-> Parser Binding -> Parser Binding
forall a b. (a -> b) -> a -> b
$ do
([(Ident, Binding)]
fields, Bool
wild) <- ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option ([], Bool
False) (ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool))
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
forall a b. (a -> b) -> a -> b
$ ParsecT String () Identity ([(Ident, Binding)], Bool)
go
Binding -> Parser Binding
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 = (ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
wildDots ParsecT String () Identity ()
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return ([], Bool
True))
ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
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) <- ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option ([],Bool
False) (ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
comma ParsecT String () Identity ()
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT String () Identity ([(Ident, Binding)], Bool)
go)
([(Ident, Binding)], Bool)
-> ParsecT String () Identity ([(Ident, Binding)], Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return ((Ident, Binding)
x(Ident, Binding) -> [(Ident, Binding)] -> [(Ident, Binding)]
forall a. a -> [a] -> [a]
:[(Ident, Binding)]
xs,Bool
wild))
recordField :: ParsecT String () Identity (Ident, Binding)
recordField = do
Ident
field <- Parser Ident
ident
Binding
p <- Binding -> Parser Binding -> Parser Binding
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)
(ParsecT String () Identity ()
forall u. ParsecT String u Identity ()
equals ParsecT String () Identity () -> Parser Binding -> Parser Binding
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser Binding
identPattern)
(Ident, Binding) -> ParsecT String () Identity (Ident, Binding)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ident
field,Binding
p)
tuplepat :: Parser Binding
tuplepat = do
[Binding]
xs <- Parser Binding
identPattern Parser Binding
-> ParsecT String () Identity ()
-> ParsecT String () Identity [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 ()
forall u. ParsecT String u Identity ()
comma
Binding -> Parser Binding
forall (m :: * -> *) a. Monad m => a -> m a
return (Binding -> Parser Binding) -> Binding -> Parser Binding
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 ([Binding] -> Binding)
-> ParsecT String () Identity [Binding] -> Parser Binding
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Binding
identPattern Parser Binding
-> ParsecT String () Identity ()
-> ParsecT String () Identity [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 ()
forall u. ParsecT String u Identity ()
comma
angle :: ParsecT String u Identity Line
angle = do
Char
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'<'
String
name' <- ParsecT String u Identity Char -> ParsecT String u Identity String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String u Identity Char
-> ParsecT String u Identity String)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
noneOf String
" \t.#\r\n!>"
let name :: String
name = if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
name' then String
"div" else String
name'
[TagPiece]
xs <- ParsecT String u Identity TagPiece
-> ParsecT String u Identity [TagPiece]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String u Identity TagPiece
-> ParsecT String u Identity [TagPiece])
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity [TagPiece]
forall a b. (a -> b) -> a -> b
$ ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall tok st a. GenParser tok st a -> GenParser tok st a
try ((ParsecT String u Identity Char -> ParsecT String u Identity String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String u Identity Char
-> ParsecT String u Identity String)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t\r\n") ParsecT String u Identity String
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
(ParsecT String u Identity TagPiece
forall u. ParsecT String u Identity TagPiece
tagIdent ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity TagPiece
forall u. ParsecT String u Identity TagPiece
tagCond ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Deref -> ParsecT String u Identity TagPiece
forall u. Maybe Deref -> ParsecT String u Identity TagPiece
tagClass Maybe Deref
forall a. Maybe a
Nothing ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT String u Identity TagPiece
forall u. ParsecT String u Identity TagPiece
tagAttrs ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
-> ParsecT String u Identity TagPiece
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Maybe Deref -> ParsecT String u Identity TagPiece
forall u. Maybe Deref -> ParsecT String u Identity TagPiece
tagAttrib Maybe Deref
forall a. Maybe a
Nothing))
String
_ <- ParsecT String u Identity Char -> ParsecT String u Identity String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String u Identity Char
-> ParsecT String u Identity String)
-> ParsecT String u Identity Char
-> ParsecT String u Identity String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
oneOf String
" \t\r\n"
Char
_ <- Char -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'>'
([Content]
c, Bool
avoidNewLines) <- ContentRule -> ParsecT String u Identity ([Content], Bool)
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' ([TagPiece]
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref]))
-> [TagPiece]
-> (String, [(Maybe Deref, String, Maybe [Content])],
[(Maybe Deref, [Content])], [Deref])
forall a b. (a -> b) -> a -> b
$ String -> TagPiece
TagName String
name TagPiece -> [TagPiece] -> [TagPiece]
forall a. a -> [a] -> [a]
: [TagPiece]
xs
if Char
'/' Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
tn
then String -> ParsecT String u Identity Line
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 Line -> ParsecT String u Identity Line
forall (m :: * -> *) a. Monad m => a -> m a
return (Line -> ParsecT String u Identity Line)
-> Line -> ParsecT String u Identity Line
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
(Int -> TagPiece -> ShowS)
-> (TagPiece -> String) -> ([TagPiece] -> ShowS) -> Show TagPiece
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') = ((Int, Line) -> Bool)
-> [(Int, Line)] -> ([(Int, Line)], [(Int, Line)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (\(Int
i', Line
_) -> Int
i' Int -> Int -> Bool
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) Nest -> [Nest] -> [Nest]
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
(Int -> Doc -> ShowS)
-> (Doc -> String) -> ([Doc] -> ShowS) -> Show Doc
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
(Doc -> Doc -> Bool) -> (Doc -> Doc -> Bool) -> Eq Doc
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]
(Int -> ReadS Doc)
-> ReadS [Doc] -> ReadPrec Doc -> ReadPrec [Doc] -> Read 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
DataType
Constr
Typeable Doc
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc)
-> (Doc -> Constr)
-> (Doc -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Doc -> Doc)
-> (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 u. (forall d. Data d => d -> u) -> Doc -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc)
-> Data Doc
Doc -> DataType
Doc -> Constr
(forall b. Data b => b -> b) -> Doc -> Doc
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cDocContent :: Constr
$cDocCase :: Constr
$cDocMaybe :: Constr
$cDocCond :: Constr
$cDocWith :: Constr
$cDocForall :: Constr
$tDoc :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Doc -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
gmapQ :: (forall d. Data d => d -> u) -> Doc -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Doc -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Doc
Data, Typeable)
nestToDoc :: HamletSettings -> [Nest] -> Result [Doc]
nestToDoc :: HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
_set [] = [Doc] -> Result [Doc]
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
[Doc] -> Result [Doc]
forall a. a -> Result a
Ok ([Doc] -> Result [Doc]) -> [Doc] -> Result [Doc]
forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> [Doc] -> Doc
DocForall Deref
d Binding
i [Doc]
inside' Doc -> [Doc] -> [Doc]
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
[Doc] -> Result [Doc]
forall a. a -> Result a
Ok ([Doc] -> Result [Doc]) -> [Doc] -> Result [Doc]
forall a b. (a -> b) -> a -> b
$ [(Deref, Binding)] -> [Doc] -> Doc
DocWith [(Deref, Binding)]
dis [Doc]
inside' Doc -> [Doc] -> [Doc]
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'
[Doc] -> Result [Doc]
forall a. a -> Result a
Ok ([Doc] -> Result [Doc]) -> [Doc] -> Result [Doc]
forall a b. (a -> b) -> a -> b
$ [(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond [(Deref, [Doc])]
ifs Maybe [Doc]
el Doc -> [Doc] -> [Doc]
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
(Maybe [Doc], [Nest]) -> Result (Maybe [Doc], [Nest])
forall (m :: * -> *) a. Monad m => a -> m a
return ([Doc] -> Maybe [Doc]
forall a. a -> Maybe a
Just [Doc]
ninside', [Nest]
x)
[Nest]
_ -> (Maybe [Doc], [Nest]) -> Result (Maybe [Doc], [Nest])
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe [Doc]
forall a. Maybe a
Nothing, [Nest]
rest)
[Doc]
rest'' <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set [Nest]
rest'
[Doc] -> Result [Doc]
forall a. a -> Result a
Ok ([Doc] -> Result [Doc]) -> [Doc] -> Result [Doc]
forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> [Doc] -> Maybe [Doc] -> Doc
DocMaybe Deref
d Binding
i [Doc]
inside' Maybe [Doc]
nothing Doc -> [Doc] -> [Doc]
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
(Binding, [Doc]) -> Result (Binding, [Doc])
forall a. a -> Result a
Ok (Binding
x, [Doc]
insideC')
getOf Nest
_ = String -> Result (Binding, [Doc])
forall v. String -> Result v
Error String
"Inside a $case there may only be $of. Use '$of _' for a wildcard."
[(Binding, [Doc])]
cases <- (Nest -> Result (Binding, [Doc]))
-> [Nest] -> Result [(Binding, [Doc])]
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
[Doc] -> Result [Doc]
forall a. a -> Result a
Ok ([Doc] -> Result [Doc]) -> [Doc] -> Result [Doc]
forall a b. (a -> b) -> a -> b
$ Deref -> [(Binding, [Doc])] -> Doc
DocCase Deref
d [(Binding, [Doc])]
cases Doc -> [Doc] -> [Doc]
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, [(Maybe a
forall a. Maybe a
Nothing, b
z)])
let takeClass :: (a, String, Maybe [a]) -> Maybe (a, [a])
takeClass (a
a, String
"class", Maybe [a]
b) = (a, [a]) -> Maybe (a, [a])
forall a. a -> Maybe a
Just (a
a, [a] -> Maybe [a] -> [a]
forall a. a -> Maybe a -> a
fromMaybe [] Maybe [a]
b)
takeClass (a, String, Maybe [a])
_ = Maybe (a, [a])
forall a. Maybe a
Nothing
let clazzes :: [(Maybe Deref, [Content])]
clazzes = [(Maybe Deref, [Content])]
classes [(Maybe Deref, [Content])]
-> [(Maybe Deref, [Content])] -> [(Maybe Deref, [Content])]
forall a. [a] -> [a] -> [a]
++ ((Maybe Deref, String, Maybe [Content])
-> Maybe (Maybe Deref, [Content]))
-> [(Maybe Deref, String, Maybe [Content])]
-> [(Maybe Deref, [Content])]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Maybe Deref, String, Maybe [Content])
-> Maybe (Maybe Deref, [Content])
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 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"class"
let noclass :: [(Maybe Deref, String, Maybe [Content])]
noclass = ((Maybe Deref, String, Maybe [Content]) -> Bool)
-> [(Maybe Deref, String, Maybe [Content])]
-> [(Maybe Deref, String, Maybe [Content])]
forall a. (a -> Bool) -> [a] -> [a]
filter (Maybe Deref, String, Maybe [Content]) -> Bool
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
[] -> ((Maybe Deref, String, Maybe [Content])
-> (Maybe Deref, String, [(Maybe Deref, Maybe [Content])]))
-> [(Maybe Deref, String, Maybe [Content])]
-> [(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Deref, String, Maybe [Content])
-> (Maybe Deref, String, [(Maybe Deref, Maybe [Content])])
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", ((Maybe Deref, [Content]) -> (Maybe Deref, Maybe [Content]))
-> [(Maybe Deref, [Content])] -> [(Maybe Deref, Maybe [Content])]
forall a b. (a -> b) -> [a] -> [b]
map (([Content] -> Maybe [Content])
-> (Maybe Deref, [Content]) -> (Maybe Deref, Maybe [Content])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second [Content] -> Maybe [Content]
forall a. a -> Maybe a
Just) [(Maybe Deref, [Content])]
clazzes)
(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])
-> [(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])]
-> [(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])]
forall a. a -> [a] -> [a]
: ((Maybe Deref, String, Maybe [Content])
-> (Maybe Deref, String, [(Maybe Deref, Maybe [Content])]))
-> [(Maybe Deref, String, Maybe [Content])]
-> [(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])]
forall a b. (a -> b) -> [a] -> [b]
map (Maybe Deref, String, Maybe [Content])
-> (Maybe Deref, String, [(Maybe Deref, Maybe [Content])])
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 ([Content] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Content]
content) Bool -> Bool -> Bool
|| Bool -> Bool
not ([Nest] -> Bool
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 (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ String
"</" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
tn String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
">"
CloseStyle
_ -> Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
""
seal :: Doc
seal = case CloseStyle
closeStyle of
CloseStyle
CloseInside -> Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
"/>"
CloseStyle
_ -> Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
">"
start :: Doc
start = Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ String
"<" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
tn
attrs'' :: [Doc]
attrs'' = ((Maybe Deref, String, [(Maybe Deref, Maybe [Content])]) -> [Doc])
-> [(Maybe Deref, String, [(Maybe Deref, Maybe [Content])])]
-> [Doc]
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 (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw
(String -> Content) -> String -> Content
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
[Doc] -> Result [Doc]
forall a. a -> Result a
Ok ([Doc] -> Result [Doc]) -> [Doc] -> Result [Doc]
forall a b. (a -> b) -> a -> b
$ Doc
start
Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [Doc]
attrs''
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (Deref -> Doc) -> [Deref] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map (Content -> Doc
DocContent (Content -> Doc) -> (Deref -> Content) -> Deref -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Deref -> Content
ContentAttrs) [Deref]
attrsD
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ Doc
seal
Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (Content -> Doc) -> [Content] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent [Content]
content
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
inside'
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ Doc
end
Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: Doc
newline'
Doc -> [Doc] -> [Doc]
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 (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw
(String -> Content) -> String -> Content
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
[Doc] -> Result [Doc]
forall a. a -> Result a
Ok ([Doc] -> Result [Doc]) -> [Doc] -> Result [Doc]
forall a b. (a -> b) -> a -> b
$ (Content -> Doc) -> [Content] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent [Content]
content [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ Doc
newline'Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
:[Doc]
inside' [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
rest'
nestToDoc HamletSettings
_set (Nest (LineElseIf Deref
_) [Nest]
_:[Nest]
_) = String -> Result [Doc]
forall v. String -> Result v
Error String
"Unexpected elseif"
nestToDoc HamletSettings
_set (Nest Line
LineElse [Nest]
_:[Nest]
_) = String -> Result [Doc]
forall v. String -> Result v
Error String
"Unexpected else"
nestToDoc HamletSettings
_set (Nest Line
LineNothing [Nest]
_:[Nest]
_) = String -> Result [Doc]
forall v. String -> Result v
Error String
"Unexpected nothing"
nestToDoc HamletSettings
_set (Nest (LineOf Binding
_) [Nest]
_:[Nest]
_) = String -> Result [Doc]
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) Doc -> [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) Doc -> [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) (([Doc] -> [Doc]) -> Maybe [Doc] -> Maybe [Doc]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Doc] -> [Doc]
compressDoc Maybe [Doc]
mnothing)
Doc -> [Doc] -> [Doc]
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 Deref -> Deref -> Bool
forall a. Eq a => a -> a -> Bool
== Deref
b = [Doc] -> [Doc]
compressDoc ([Doc] -> [Doc]) -> [Doc] -> [Doc]
forall a b. (a -> b) -> a -> b
$ [(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond [(Deref
a, [Doc]
x [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Doc]
y)] Maybe [Doc]
forall a. Maybe a
Nothing Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [Doc]
rest
compressDoc (DocCond [(Deref, [Doc])]
x Maybe [Doc]
y:[Doc]
rest) =
[(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond (((Deref, [Doc]) -> (Deref, [Doc]))
-> [(Deref, [Doc])] -> [(Deref, [Doc])]
forall a b. (a -> b) -> [a] -> [b]
map (([Doc] -> [Doc]) -> (Deref, [Doc]) -> (Deref, [Doc])
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 ([Doc] -> [Doc]) -> Maybe [Doc] -> Maybe [Doc]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Maybe [Doc]
y)
Doc -> [Doc] -> [Doc]
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 (((Binding, [Doc]) -> (Binding, [Doc]))
-> [(Binding, [Doc])] -> [(Binding, [Doc])]
forall a b. (a -> b) -> [a] -> [b]
map (([Doc] -> [Doc]) -> (Binding, [Doc]) -> (Binding, [Doc])
forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second [Doc] -> [Doc]
compressDoc) [(Binding, [Doc])]
cs) Doc -> [Doc] -> [Doc]
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 ([Doc] -> [Doc]) -> [Doc] -> [Doc]
forall a b. (a -> b) -> a -> b
$ (Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ String
x String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
y) Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: [Doc]
rest
compressDoc (DocContent Content
x:[Doc]
rest) = Content -> Doc
DocContent Content
x Doc -> [Doc] -> [Doc]
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 ([(Int, Line)] -> [Nest]) -> [(Int, Line)] -> [Nest]
forall a b. (a -> b) -> a -> b
$ ((Int, Line) -> Bool) -> [(Int, Line)] -> [(Int, Line)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int, Line) -> Bool
forall a. (a, Line) -> Bool
notEmpty [(Int, Line)]
ls
[Doc]
ds <- HamletSettings -> [Nest] -> Result [Doc]
nestToDoc HamletSettings
set' [Nest]
ns
(Maybe NewlineStyle, [Doc]) -> Result (Maybe NewlineStyle, [Doc])
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 (Maybe Deref
forall a. Maybe a
Nothing, String
k, [(Maybe Deref, Maybe [Content])]
v))] Maybe [Doc]
forall a. Maybe a
Nothing]
attrToContent (Maybe Deref
Nothing, String
k, []) = [Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ Char
' ' Char -> ShowS
forall a. a -> [a] -> [a]
: String
k]
attrToContent (Maybe Deref
Nothing, String
k, [(Maybe Deref
Nothing, Maybe [Content]
Nothing)]) = [Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw (String -> Content) -> String -> Content
forall a b. (a -> b) -> a -> b
$ Char
' ' Char -> ShowS
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
' ' Char -> ShowS
forall a. a -> [a] -> [a]
: String
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"=\""))
Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: (Content -> Doc) -> [Content] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent [Content]
v
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
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
' ' Char -> ShowS
forall a. a -> [a] -> [a]
: String
k String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"=\""))
Doc -> [Doc] -> [Doc]
forall a. a -> [a] -> [a]
: ((Maybe Deref, Maybe [Content]) -> [Doc])
-> [(Maybe Deref, Maybe [Content])] -> [Doc]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Maybe Deref, Maybe [Content]) -> [Doc]
go ([(Maybe Deref, Maybe [Content])]
-> [(Maybe Deref, Maybe [Content])]
forall a. [a] -> [a]
init [(Maybe Deref, Maybe [Content])]
v)
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ (Maybe Deref, Maybe [Content]) -> [Doc]
go' ([(Maybe Deref, Maybe [Content])] -> (Maybe Deref, Maybe [Content])
forall a. [a] -> a
last [(Maybe Deref, Maybe [Content])]
v)
[Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
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) = (Content -> Doc) -> [Content] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent ([Content] -> Maybe [Content] -> [Content]
forall a. a -> Maybe a -> a
fromMaybe [] Maybe [Content]
x) [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
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, (Content -> Doc) -> [Content] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent ([Content] -> Maybe [Content] -> [Content]
forall a. a -> Maybe a -> a
fromMaybe [] Maybe [Content]
x) [Doc] -> [Doc] -> [Doc]
forall a. [a] -> [a] -> [a]
++ [Content -> Doc
DocContent (Content -> Doc) -> Content -> Doc
forall a b. (a -> b) -> a -> b
$ String -> Content
ContentRaw String
" "])]
Maybe [Doc]
forall a. Maybe a
Nothing
]
go' :: (Maybe Deref, Maybe [Content]) -> [Doc]
go' (Maybe Deref
Nothing, Maybe [Content]
x) = [Doc] -> ([Content] -> [Doc]) -> Maybe [Content] -> [Doc]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ((Content -> Doc) -> [Content] -> [Doc]
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, [Doc] -> ([Content] -> [Doc]) -> Maybe [Content] -> [Doc]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ((Content -> Doc) -> [Content] -> [Doc]
forall a b. (a -> b) -> [a] -> [b]
map Content -> Doc
DocContent) Maybe [Content]
x)]
Maybe [Doc]
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 HamletSettings -> Q Exp
HamletSettings -> Q (TExp HamletSettings)
(HamletSettings -> Q Exp)
-> (HamletSettings -> Q (TExp HamletSettings))
-> Lift HamletSettings
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: HamletSettings -> Q (TExp HamletSettings)
$cliftTyped :: HamletSettings -> Q (TExp HamletSettings)
lift :: HamletSettings -> Q Exp
$clift :: HamletSettings -> Q Exp
Lift
data NewlineStyle = NoNewlines
| NewlinesText
| AlwaysNewlines
| DefaultNewlineStyle
deriving (Int -> NewlineStyle -> ShowS
[NewlineStyle] -> ShowS
NewlineStyle -> String
(Int -> NewlineStyle -> ShowS)
-> (NewlineStyle -> String)
-> ([NewlineStyle] -> ShowS)
-> Show NewlineStyle
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, NewlineStyle -> Q Exp
NewlineStyle -> Q (TExp NewlineStyle)
(NewlineStyle -> Q Exp)
-> (NewlineStyle -> Q (TExp NewlineStyle)) -> Lift NewlineStyle
forall t. (t -> Q Exp) -> (t -> Q (TExp t)) -> Lift t
liftTyped :: NewlineStyle -> Q (TExp NewlineStyle)
$cliftTyped :: NewlineStyle -> Q (TExp NewlineStyle)
lift :: NewlineStyle -> Q Exp
$clift :: NewlineStyle -> Q Exp
Lift)
instance Lift (String -> CloseStyle) where
lift :: (String -> CloseStyle) -> Q Exp
lift String -> CloseStyle
_ = [|\s -> htmlCloseStyle s|]
#if MIN_VERSION_template_haskell(2,17,0)
liftTyped = unsafeCodeCoerce . lift
#elif MIN_VERSION_template_haskell(2,16,0)
liftTyped :: (String -> CloseStyle) -> Q (TExp (String -> CloseStyle))
liftTyped = Q Exp -> Q (TExp (String -> CloseStyle))
forall a. Q Exp -> Q (TExp a)
unsafeTExpCoerce (Q Exp -> Q (TExp (String -> CloseStyle)))
-> ((String -> CloseStyle) -> Q Exp)
-> (String -> CloseStyle)
-> Q (TExp (String -> CloseStyle))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> CloseStyle) -> Q Exp
forall t. Lift t => t -> Q Exp
lift
#endif
htmlEmptyTags :: Set String
htmlEmptyTags :: Set String
htmlEmptyTags = [String] -> Set String
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\" " String -> ShowS
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 String -> Set String -> Bool
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 String -> Set String -> Bool
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
([(Deref, [Doc])], Maybe [Doc], [Nest])
-> Result ([(Deref, [Doc])], Maybe [Doc], [Nest])
forall a. a -> Result a
Ok ([(Deref, [Doc])] -> [(Deref, [Doc])]
front [], [Doc] -> Maybe [Doc]
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 ([(Deref, [Doc])] -> [(Deref, [Doc])])
-> ([(Deref, [Doc])] -> [(Deref, [Doc])])
-> [(Deref, [Doc])]
-> [(Deref, [Doc])]
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 = ([(Deref, [Doc])], Maybe [Doc], [Nest])
-> Result ([(Deref, [Doc])], Maybe [Doc], [Nest])
forall a. a -> Result a
Ok ([(Deref, [Doc])] -> [(Deref, [Doc])]
front [], Maybe [Doc]
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
(Binding -> Binding -> Bool)
-> (Binding -> Binding -> Bool) -> Eq Binding
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
(Int -> Binding -> ShowS)
-> (Binding -> String) -> ([Binding] -> ShowS) -> Show Binding
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]
(Int -> ReadS Binding)
-> ReadS [Binding]
-> ReadPrec Binding
-> ReadPrec [Binding]
-> Read 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
DataType
Constr
Typeable Binding
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding -> c Binding)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Binding)
-> (Binding -> Constr)
-> (Binding -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Binding -> Binding)
-> (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 u. (forall d. Data d => d -> u) -> Binding -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Binding -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding -> m Binding)
-> Data Binding
Binding -> DataType
Binding -> Constr
(forall b. Data b => b -> b) -> Binding -> Binding
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding -> c Binding
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cBindRecord :: Constr
$cBindList :: Constr
$cBindTuple :: Constr
$cBindConstr :: Constr
$cBindAs :: Constr
$cBindVar :: Constr
$tBinding :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Binding -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binding -> u
gmapQ :: (forall d. Data d => d -> u) -> Binding -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Binding -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Binding
Data, Typeable)
data DataConstr = DCQualified Module Ident
| DCUnqualified Ident
deriving (DataConstr -> DataConstr -> Bool
(DataConstr -> DataConstr -> Bool)
-> (DataConstr -> DataConstr -> Bool) -> Eq DataConstr
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
(Int -> DataConstr -> ShowS)
-> (DataConstr -> String)
-> ([DataConstr] -> ShowS)
-> Show DataConstr
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]
(Int -> ReadS DataConstr)
-> ReadS [DataConstr]
-> ReadPrec DataConstr
-> ReadPrec [DataConstr]
-> Read 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
DataType
Constr
Typeable DataConstr
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataConstr -> c DataConstr)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c DataConstr)
-> (DataConstr -> Constr)
-> (DataConstr -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> DataConstr -> DataConstr)
-> (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 u. (forall d. Data d => d -> u) -> DataConstr -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> DataConstr -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> DataConstr -> m DataConstr)
-> Data DataConstr
DataConstr -> DataType
DataConstr -> Constr
(forall b. Data b => b -> b) -> DataConstr -> DataConstr
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> DataConstr -> c DataConstr
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cDCUnqualified :: Constr
$cDCQualified :: Constr
$tDataConstr :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> DataConstr -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> DataConstr -> u
gmapQ :: (forall d. Data d => d -> u) -> DataConstr -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> DataConstr -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable DataConstr
Data, Typeable)
newtype Module = Module [String]
deriving (Module -> Module -> Bool
(Module -> Module -> Bool)
-> (Module -> Module -> Bool) -> Eq Module
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
(Int -> Module -> ShowS)
-> (Module -> String) -> ([Module] -> ShowS) -> Show Module
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]
(Int -> ReadS Module)
-> ReadS [Module]
-> ReadPrec Module
-> ReadPrec [Module]
-> Read 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
DataType
Constr
Typeable Module
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Module -> c Module)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Module)
-> (Module -> Constr)
-> (Module -> DataType)
-> (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))
-> ((forall b. Data b => b -> b) -> Module -> Module)
-> (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 u. (forall d. Data d => d -> u) -> Module -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Module -> u)
-> (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 (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Module -> m Module)
-> Data Module
Module -> DataType
Module -> Constr
(forall b. Data b => b -> b) -> Module -> Module
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Module -> c Module
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c 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)
$cModule :: Constr
$tModule :: DataType
gmapMo :: (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 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 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 :: Int -> (forall d. Data d => d -> u) -> Module -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Module -> u
gmapQ :: (forall d. Data d => d -> u) -> Module -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Module -> [u]
gmapQr :: (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 :: (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 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 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 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 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
$cp1Data :: Typeable Module
Data, Typeable)
spaceTabs :: Parser String
spaceTabs :: GenParser Char () String
spaceTabs = ParsecT String () Identity Char -> GenParser Char () String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT String () Identity Char -> GenParser Char () String)
-> ParsecT String () Identity Char -> GenParser Char () String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT String () Identity Char
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
| ((Maybe Deref, [Content]) -> Bool)
-> [(Maybe Deref, [Content])] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Maybe Deref -> Bool
forall a. Maybe a -> Bool
isNothing (Maybe Deref -> Bool)
-> ((Maybe Deref, [Content]) -> Maybe Deref)
-> (Maybe Deref, [Content])
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Deref, [Content]) -> Maybe Deref
forall a b. (a, b) -> a
fst) [(Maybe Deref, [Content])]
cs = Maybe Deref
forall a. Maybe a
Nothing
| Bool
otherwise = Deref -> Maybe Deref
forall a. a -> Maybe a
Just (Deref -> Maybe Deref) -> Deref -> Maybe Deref
forall a b. (a -> b) -> a -> b
$ Deref -> Deref -> Deref
DerefBranch (Ident -> Deref
DerefIdent Ident
specialOrIdent) (Deref -> Deref) -> Deref -> Deref
forall a b. (a -> b) -> a -> b
$ [Deref] -> Deref
DerefList ([Deref] -> Deref) -> [Deref] -> Deref
forall a b. (a -> b) -> a -> b
$ ((Maybe Deref, [Content]) -> Maybe Deref)
-> [(Maybe Deref, [Content])] -> [Deref]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Maybe Deref, [Content]) -> Maybe Deref
forall a b. (a, b) -> a
fst [(Maybe Deref, [Content])]
cs
specialOrIdent :: Ident
specialOrIdent :: Ident
specialOrIdent = String -> Ident
Ident String
"__or__hamlet__special"