module Text.Docvim.Visitor.Section ( injectCommands
, injectFunctions
, injectMappings
, injectOptions
) where
import Control.Lens
import Control.Monad.State
import Data.Data.Lens
import Text.Docvim.AST
data SectionInfo = SectionInfo { _hasCommand :: Bool
, _hasCommands :: Bool
, _hasFunction :: Bool
, _hasFunctions :: Bool
, _hasMapping :: Bool
, _hasMappings :: Bool
, _hasOption :: Bool
, _hasOptions :: Bool
} deriving (Show)
makeLenses ''SectionInfo
defaultSectionInfo :: SectionInfo
defaultSectionInfo = SectionInfo { _hasCommand = False
, _hasCommands = False
, _hasFunction = False
, _hasFunctions = False
, _hasMapping = False
, _hasMappings = False
, _hasOption = False
, _hasOptions = False
}
getSectionInfo :: Node -> SectionInfo
getSectionInfo n = execState (mapMOf_ (cosmosOf uniplate) check n) defaultSectionInfo
where
check CommandAnnotation {} = hasCommand .= True
check CommandsAnnotation = hasCommands .= True
check (FunctionAnnotation _) = hasFunction .= True
check FunctionsAnnotation = hasFunctions .= True
check (MappingAnnotation _) = hasMapping .= True
check MappingsAnnotation = hasMappings .= True
check OptionAnnotation {} = hasOption .= True
check OptionsAnnotation = hasOptions .= True
check _ = modify id
inject :: Node -> Node -> Node
inject (Project ns) n = Project $ ns ++ [DocBlock [n]]
inject other _ = other
injectCommands :: Node -> Node
injectCommands n =
if | getSectionInfo n ^. hasCommands -> n
| getSectionInfo n ^. hasCommand -> inject n CommandsAnnotation
| otherwise -> n
injectFunctions :: Node -> Node
injectFunctions n =
if | getSectionInfo n ^. hasFunctions -> n
| getSectionInfo n ^. hasFunction -> inject n FunctionsAnnotation
| otherwise -> n
injectMappings :: Node -> Node
injectMappings n =
if | getSectionInfo n ^. hasMappings -> n
| getSectionInfo n ^. hasMapping -> inject n MappingsAnnotation
| otherwise -> n
injectOptions :: Node -> Node
injectOptions n =
if | getSectionInfo n ^. hasOptions -> n
| getSectionInfo n ^. hasOption -> inject n OptionsAnnotation
| otherwise -> n