Skip to content

Commit

Permalink
Adds documentation and styling.
Browse files Browse the repository at this point in the history
  • Loading branch information
Laar committed Mar 27, 2013
1 parent fd727e9 commit 6dccf87
Showing 1 changed file with 29 additions and 0 deletions.
29 changes: 29 additions & 0 deletions src/Interface/Module.hs
@@ -1,9 +1,26 @@
-----------------------------------------------------------------------------
--
-- Module : Interface.Module
-- Copyright : (c) 2013 Lars Corbijn
-- License : BSD-style (see the file /LICENSE)
--
-- Maintainer :
-- Stability :
-- Portability :
--
-- | The interface writing part of the generator.
--
-----------------------------------------------------------------------------

module Interface.Module ( module Interface.Module (
moduleToInterface, writeModuleInterface, moduleToInterface, writeModuleInterface,
writePackageInterface, writePackageInterface,
verifyInterface, verifyInterface,
) where ) where


-----------------------------------------------------------------------------


import Control.Monad import Control.Monad
import Language.Haskell.Exts.Syntax import Language.Haskell.Exts.Syntax
import Data.List import Data.List
Expand All @@ -17,17 +34,22 @@ import Main.Monad
import Main.Options import Main.Options
import Modules.Types import Modules.Types


-----------------------------------------------------------------------------

-- | Writes the package/index interface file.
writePackageInterface :: [RawModule] -> RawGenIO () writePackageInterface :: [RawModule] -> RawGenIO ()
writePackageInterface modus = do writePackageInterface modus = do
let inter = OpenGLRawI . S.fromList $ map rawModuleName modus let inter = OpenGLRawI . S.fromList $ map rawModuleName modus
path <- asksOptions interfaceDir path <- asksOptions interfaceDir
liftIO $ writePackage path inter liftIO $ writePackage path inter


-- | Writes the interface file for a single `RawModule`.
writeModuleInterface :: RawModule -> RawGenIO () writeModuleInterface :: RawModule -> RawGenIO ()
writeModuleInterface modu = do writeModuleInterface modu = do
path <- asksOptions interfaceDir path <- asksOptions interfaceDir
liftIO . writeModule path $ moduleToInterface modu liftIO . writeModule path $ moduleToInterface modu


-- | Converts a single module to its interface representation.
moduleToInterface :: RawModule -> ModuleI moduleToInterface :: RawModule -> ModuleI
moduleToInterface rm = moduleToInterface rm =
let baseModule let baseModule
Expand All @@ -36,6 +58,7 @@ moduleToInterface rm =
S.empty S.empty S.empty S.empty S.empty S.empty
in foldl' (flip addModulePart) baseModule $ rawModuleParts rm in foldl' (flip addModulePart) baseModule $ rawModuleParts rm


-- | Adds a `ModulePart` to the interface of a module.
addModulePart :: ModulePart -> ModuleI -> ModuleI addModulePart :: ModulePart -> ModuleI -> ModuleI
addModulePart p m = case p of addModulePart p m = case p of
DefineEnum n gln t _ -> addEnum $ EnumI gln (unName n) t DefineEnum n gln t _ -> addEnum $ EnumI gln (unName n) t
Expand All @@ -51,6 +74,9 @@ addModulePart p m = case p of
unName (Ident i) = i unName (Ident i) = i
unName (Symbol s) = s unName (Symbol s) = s


-----------------------------------------------------------------------------

-- | Performs some simple checks on the interface files.
verifyInterface :: [RawModule] -> RawGenIO () verifyInterface :: [RawModule] -> RawGenIO ()
verifyInterface rmods = do verifyInterface rmods = do
let rmodNames = S.fromList $ map rawModuleName rmods let rmodNames = S.fromList $ map rawModuleName rmods
Expand All @@ -69,6 +95,7 @@ verifyInterface rmods = do
where where
unmodName (ModuleName mn) = mn unmodName (ModuleName mn) = mn


-- | Verification of a single module from the interface.
verifyModule :: ModuleName -> RawGenIO () verifyModule :: ModuleName -> RawGenIO ()
verifyModule mn = do verifyModule mn = do
iDir <- asksOptions interfaceDir iDir <- asksOptions interfaceDir
Expand All @@ -77,3 +104,5 @@ verifyModule mn = do
where where
errMsg = "Module interface parsing failed for: " ++ mName errMsg = "Module interface parsing failed for: " ++ mName
(ModuleName mName) = mn (ModuleName mName) = mn

-----------------------------------------------------------------------------

0 comments on commit 6dccf87

Please sign in to comment.