{-# LANGUAGE TypeFamilies #-}
module Drasil.GOOL.RendererClassesProc (
ProcRenderSym, RenderFile(..), RenderMod(..), ModuleElim(..),
ProcRenderMethod(..)
) where
import Drasil.GOOL.InterfaceCommon (Label, SMethod, MSParameter,
MSBody, BlockSym(..), VisibilitySym(..))
import qualified Drasil.GOOL.InterfaceProc as IP (SFile, FSModule, FileSym(..),
ModuleSym(..))
import Drasil.GOOL.State (FS)
import Text.PrettyPrint.HughesPJ (Doc)
import Drasil.GOOL.RendererClassesCommon (CommonRenderSym, BlockCommentSym(..),
RenderMethod(..), MSMthdType)
class (CommonRenderSym r, IP.FileSym r, RenderFile r, RenderMod r, ModuleElim r,
ProcRenderMethod r
) => ProcRenderSym r
class (BlockCommentSym r) => RenderFile r where
top :: r (IP.Module r) -> r (Block r)
bottom :: r (Block r)
:: IP.SFile r -> FS (r (BlockComment r)) -> IP.SFile r
fileFromData :: FilePath -> IP.FSModule r -> IP.SFile r
class RenderMod r where
modFromData :: String -> FS Doc -> IP.FSModule r
updateModuleDoc :: (Doc -> Doc) -> r (IP.Module r) -> r (IP.Module r)
class ModuleElim r where
module' :: r (IP.Module r) -> Doc
class (RenderMethod r) => ProcRenderMethod r where
intFunc :: Bool -> Label -> r (Visibility r) -> MSMthdType r ->
[MSParameter r] -> MSBody r -> SMethod r