{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TemplateHaskell #-}

module Text.Heterocephalus.Parse.Doc where

#if MIN_VERSION_base(4,9,0)
#else
import Control.Applicative ((*>), (<*), pure)
#endif
import Control.Monad (void)
import Data.Data (Data)
import Data.Typeable (Typeable)
import Text.Parsec
       (Parsec, ParseError, SourcePos, (<|>), eof, incSourceLine, many,
        many1, optional, optionMaybe, parse, tokenPrim)
import Text.Shakespeare.Base (Deref)

import Text.Hamlet.Parse
import Text.Heterocephalus.Parse.Control (Content(..), Control(..))

data Doc = DocForall Deref Binding [Doc]
         | DocCond [(Deref, [Doc])] (Maybe [Doc])
         | DocCase Deref [(Binding, [Doc])]
         | DocContent Content
    deriving (Typeable Doc
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 a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
forall u. (forall d. Data d => d -> u) -> Doc -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Doc -> m Doc
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Doc -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Doc -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Doc -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Doc -> r
gmapT :: (forall b. Data b => b -> b) -> Doc -> Doc
$cgmapT :: (forall b. Data b => b -> b) -> Doc -> Doc
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Doc)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Doc)
dataTypeOf :: Doc -> DataType
$cdataTypeOf :: Doc -> DataType
toConstr :: Doc -> Constr
$ctoConstr :: Doc -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Doc
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Doc -> c Doc
Data, 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, 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, Typeable)

type DocParser = Parsec [Control] ()

parseDocFromControls :: [Control] -> Either ParseError [Doc]
parseDocFromControls :: [Control] -> Either ParseError [Doc]
parseDocFromControls = Parsec [Control] () [Doc]
-> String -> [Control] -> Either ParseError [Doc]
forall s t a.
Stream s Identity t =>
Parsec s () a -> String -> s -> Either ParseError a
parse (Parsec [Control] () [Doc]
docsParser Parsec [Control] () [Doc]
-> ParsecT [Control] () Identity () -> Parsec [Control] () [Doc]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Control] () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof) String
""

docsParser :: DocParser [Doc]
docsParser :: Parsec [Control] () [Doc]
docsParser = ParsecT [Control] () Identity Doc -> Parsec [Control] () [Doc]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT [Control] () Identity Doc
docParser

docParser :: DocParser Doc
docParser :: ParsecT [Control] () Identity Doc
docParser = ParsecT [Control] () Identity Doc
forallDoc ParsecT [Control] () Identity Doc
-> ParsecT [Control] () Identity Doc
-> ParsecT [Control] () Identity Doc
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [Control] () Identity Doc
condDoc ParsecT [Control] () Identity Doc
-> ParsecT [Control] () Identity Doc
-> ParsecT [Control] () Identity Doc
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [Control] () Identity Doc
caseDoc ParsecT [Control] () Identity Doc
-> ParsecT [Control] () Identity Doc
-> ParsecT [Control] () Identity Doc
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT [Control] () Identity Doc
contentDoc

forallDoc :: DocParser Doc
forallDoc :: ParsecT [Control] () Identity Doc
forallDoc = do
  ControlForall Deref
deref Binding
binding <- DocParser Control
forallControlStatement
  [Doc]
innerDocs <- Parsec [Control] () [Doc]
docsParser
  DocParser Control -> ParsecT [Control] () Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void DocParser Control
endforallControlStatement
  Doc -> ParsecT [Control] () Identity Doc
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Doc -> ParsecT [Control] () Identity Doc)
-> Doc -> ParsecT [Control] () Identity Doc
forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> [Doc] -> Doc
DocForall Deref
deref Binding
binding [Doc]
innerDocs

condDoc :: DocParser Doc
condDoc :: ParsecT [Control] () Identity Doc
condDoc = do
  ControlIf Deref
ifDeref <- DocParser Control
ifControlStatement
  [Doc]
ifInnerDocs <- Parsec [Control] () [Doc]
docsParser
  [(Deref, [Doc])]
elseIfs <- DocParser [(Deref, [Doc])]
condElseIfs
  Maybe [Doc]
maybeElseInnerDocs <- Parsec [Control] () [Doc]
-> ParsecT [Control] () Identity (Maybe [Doc])
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe (Parsec [Control] () [Doc]
 -> ParsecT [Control] () Identity (Maybe [Doc]))
-> Parsec [Control] () [Doc]
-> ParsecT [Control] () Identity (Maybe [Doc])
forall a b. (a -> b) -> a -> b
$ DocParser Control
elseControlStatement DocParser Control
-> Parsec [Control] () [Doc] -> Parsec [Control] () [Doc]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parsec [Control] () [Doc]
docsParser
  DocParser Control -> ParsecT [Control] () Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void DocParser Control
endifControlStatement
  let allConds :: [(Deref, [Doc])]
allConds = (Deref
ifDeref, [Doc]
ifInnerDocs) (Deref, [Doc]) -> [(Deref, [Doc])] -> [(Deref, [Doc])]
forall a. a -> [a] -> [a]
: [(Deref, [Doc])]
elseIfs
  Doc -> ParsecT [Control] () Identity Doc
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Doc -> ParsecT [Control] () Identity Doc)
-> Doc -> ParsecT [Control] () Identity Doc
forall a b. (a -> b) -> a -> b
$ [(Deref, [Doc])] -> Maybe [Doc] -> Doc
DocCond [(Deref, [Doc])]
allConds Maybe [Doc]
maybeElseInnerDocs

caseDoc :: DocParser Doc
caseDoc :: ParsecT [Control] () Identity Doc
caseDoc = do
  ControlCase Deref
caseDeref <- DocParser Control
caseControlStatement
  -- Ignore a single, optional NoControl statement (with whitespace that will be
  -- ignored).
  ParsecT [Control] () Identity Doc
-> ParsecT [Control] () Identity ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT [Control] () Identity Doc
contentDoc
  [(Binding, [Doc])]
caseOfs <- ParsecT [Control] () Identity (Binding, [Doc])
-> ParsecT [Control] () Identity [(Binding, [Doc])]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT [Control] () Identity (Binding, [Doc])
 -> ParsecT [Control] () Identity [(Binding, [Doc])])
-> ParsecT [Control] () Identity (Binding, [Doc])
-> ParsecT [Control] () Identity [(Binding, [Doc])]
forall a b. (a -> b) -> a -> b
$ do
    ControlCaseOf Binding
caseBinding <- DocParser Control
caseOfControlStatement
    [Doc]
innerDocs <- Parsec [Control] () [Doc]
docsParser
    (Binding, [Doc]) -> ParsecT [Control] () Identity (Binding, [Doc])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Binding
caseBinding, [Doc]
innerDocs)
  DocParser Control -> ParsecT [Control] () Identity ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void DocParser Control
endcaseControlStatement
  Doc -> ParsecT [Control] () Identity Doc
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Doc -> ParsecT [Control] () Identity Doc)
-> Doc -> ParsecT [Control] () Identity Doc
forall a b. (a -> b) -> a -> b
$ Deref -> [(Binding, [Doc])] -> Doc
DocCase Deref
caseDeref [(Binding, [Doc])]
caseOfs

contentDoc :: DocParser Doc
contentDoc :: ParsecT [Control] () Identity Doc
contentDoc = (Control -> Maybe Doc) -> ParsecT [Control] () Identity Doc
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Doc) -> ParsecT [Control] () Identity Doc)
-> (Control -> Maybe Doc) -> ParsecT [Control] () Identity Doc
forall a b. (a -> b) -> a -> b
$ \case
  NoControl Content
content -> Doc -> Maybe Doc
forall a. a -> Maybe a
Just (Doc -> Maybe Doc) -> Doc -> Maybe Doc
forall a b. (a -> b) -> a -> b
$ Content -> Doc
DocContent Content
content
  Control
_ -> Maybe Doc
forall a. Maybe a
Nothing

condElseIfs :: DocParser [(Deref, [Doc])]
condElseIfs :: DocParser [(Deref, [Doc])]
condElseIfs = ParsecT [Control] () Identity (Deref, [Doc])
-> DocParser [(Deref, [Doc])]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT [Control] () Identity (Deref, [Doc])
 -> DocParser [(Deref, [Doc])])
-> ParsecT [Control] () Identity (Deref, [Doc])
-> DocParser [(Deref, [Doc])]
forall a b. (a -> b) -> a -> b
$ do
  ControlElseIf Deref
elseIfDeref <- DocParser Control
elseIfControlStatement
  [Doc]
elseIfInnerDocs <- Parsec [Control] () [Doc]
docsParser
  (Deref, [Doc]) -> ParsecT [Control] () Identity (Deref, [Doc])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Deref
elseIfDeref, [Doc]
elseIfInnerDocs)

ifControlStatement :: DocParser Control
ifControlStatement :: DocParser Control
ifControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  ControlIf Deref
deref -> Control -> Maybe Control
forall a. a -> Maybe a
Just (Control -> Maybe Control) -> Control -> Maybe Control
forall a b. (a -> b) -> a -> b
$ Deref -> Control
ControlIf Deref
deref
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

elseIfControlStatement :: DocParser Control
elseIfControlStatement :: DocParser Control
elseIfControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  ControlElseIf Deref
deref -> Control -> Maybe Control
forall a. a -> Maybe a
Just (Control -> Maybe Control) -> Control -> Maybe Control
forall a b. (a -> b) -> a -> b
$ Deref -> Control
ControlElseIf Deref
deref
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

elseControlStatement :: DocParser Control
elseControlStatement :: DocParser Control
elseControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  Control
ControlElse -> Control -> Maybe Control
forall a. a -> Maybe a
Just Control
ControlElse
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

endifControlStatement :: DocParser Control
endifControlStatement :: DocParser Control
endifControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  Control
ControlEndIf -> Control -> Maybe Control
forall a. a -> Maybe a
Just Control
ControlEndIf
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

caseControlStatement :: DocParser Control
caseControlStatement :: DocParser Control
caseControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  ControlCase Deref
deref -> Control -> Maybe Control
forall a. a -> Maybe a
Just (Control -> Maybe Control) -> Control -> Maybe Control
forall a b. (a -> b) -> a -> b
$ Deref -> Control
ControlCase Deref
deref
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

caseOfControlStatement :: DocParser Control
caseOfControlStatement :: DocParser Control
caseOfControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  ControlCaseOf Binding
binding -> Control -> Maybe Control
forall a. a -> Maybe a
Just (Control -> Maybe Control) -> Control -> Maybe Control
forall a b. (a -> b) -> a -> b
$ Binding -> Control
ControlCaseOf Binding
binding
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

endcaseControlStatement :: DocParser Control
endcaseControlStatement :: DocParser Control
endcaseControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  Control
ControlEndCase -> Control -> Maybe Control
forall a. a -> Maybe a
Just Control
ControlEndCase
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

forallControlStatement :: DocParser Control
forallControlStatement :: DocParser Control
forallControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  ControlForall Deref
deref Binding
binding -> Control -> Maybe Control
forall a. a -> Maybe a
Just (Control -> Maybe Control) -> Control -> Maybe Control
forall a b. (a -> b) -> a -> b
$ Deref -> Binding -> Control
ControlForall Deref
deref Binding
binding
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

endforallControlStatement :: DocParser Control
endforallControlStatement :: DocParser Control
endforallControlStatement = (Control -> Maybe Control) -> DocParser Control
forall x. (Control -> Maybe x) -> DocParser x
primControlStatement ((Control -> Maybe Control) -> DocParser Control)
-> (Control -> Maybe Control) -> DocParser Control
forall a b. (a -> b) -> a -> b
$ \case
  Control
ControlEndForall -> Control -> Maybe Control
forall a. a -> Maybe a
Just Control
ControlEndForall
  Control
_ -> Maybe Control
forall a. Maybe a
Nothing

primControlStatement :: (Control -> Maybe x)-> DocParser x
primControlStatement :: forall x. (Control -> Maybe x) -> DocParser x
primControlStatement = (Control -> String)
-> (SourcePos -> Control -> [Control] -> SourcePos)
-> (Control -> Maybe x)
-> ParsecT [Control] () Identity x
forall s (m :: * -> *) t a u.
Stream s m t =>
(t -> String)
-> (SourcePos -> t -> s -> SourcePos)
-> (t -> Maybe a)
-> ParsecT s u m a
tokenPrim Control -> String
forall a. Show a => a -> String
show SourcePos -> Control -> [Control] -> SourcePos
forall a b. SourcePos -> a -> b -> SourcePos
incSourcePos

incSourcePos :: SourcePos -> a -> b -> SourcePos
incSourcePos :: forall a b. SourcePos -> a -> b -> SourcePos
incSourcePos SourcePos
sourcePos a
_ b
_ = SourcePos -> Int -> SourcePos
incSourceLine SourcePos
sourcePos Int
1