-module OFC.Common where
+module OFC.Common
+ ( IndexType(..)
+ , PrettyPrintable(..)
+ ) where
+
import Text.PrettyPrint (Doc, renderStyle, Style(..), Mode(..))
data IndexType =
-module OFC.SecondLevel where
+module OFC.SecondLevel
+ ( SymbolTable
+ , Quantification(..)
+ , ValueType(..)
+ , Expression(..)
+ , Assignment(..)
+ , DiagonalOperator(..)
+ , OperatorExpr(..)
+ , OFL2
+ , buildSecondLevel
+ ) where
+
import OFC.Common
import OFC.TargetMapping (MappingTable, FortranFunction)
import qualified OFC.TargetMapping as TM
-module OFC.TargetMapping where
+module OFC.TargetMapping
+ ( MappingTable
+ , TargetType(..)
+ , FortranType(..)
+ , ArrayIndex(..)
+ , SpaceInfo(..)
+ , FortranParamProperty(..)
+ , PPDFunctionSetProperty(..)
+ , FortranFunction(..)
+ , FortranFunctionProperty(..)
+ , findSpace
+ , findParamType
+ ) where
+
import Data.Map (Map)
import Data.Maybe (catMaybes)
toFortranType (ParamType t) = Just t
toFortranType _ = Nothing
-
getProperty :: (Show a) => (FortranParamProperty -> Maybe a) -> [FortranParamProperty] -> Maybe a
getProperty getter properties = case catMaybes $ map getter properties of
[] -> Nothing
-module OFC.TopLevel where
+module OFC.TopLevel
+ ( BaseType(..)
+ , Expression(..)
+ , Assignment(..)
+ , SymbolTable
+ , OFL
+ , OFLKeyword(..)
+ , addIndexDeclaration
+ , addInternalIndexDeclaration
+ , addValueDeclaration
+ , addAssignment
+ , addTargetMapping
+ , getSymbols
+ , getIndexSymbols
+ , getValueSymbols
+ , getTargetMappings
+ , getTargetType
+ , getOutputFunction
+ , findUniqueName
+ , setOutputFunction
+ , getIndices
+ , getIndexType
+ , getValueType
+ , hasIndex
+ , hasTargetMapping
+ , hasSymbol
+ , hasValue
+ , isInternalSymbol
+ , promoteType
+ , getType
+ , emptyOFL
+ ) where
+
import OFC.TargetMapping
import OFC.Common
import Text.PrettyPrint
module Main (main) where
import System.Environment (getArgs)
-import OFC.Common
+import OFC.Common (prettyPrint)
import OFC.Parser (runOFLParser)
import OFC.TopLevel (OFL)
import OFC.SecondLevel (buildSecondLevel)