, integer, int, parens)
import Data.Complex (Complex(..), realPart, imagPart)
-data IndexType =
- FunctionIndex |
- SpinIndex |
- SpatialIndex
+data IndexType
+ = FunctionIndex
+ | SpinIndex
+ | SpatialIndex
deriving (Show, Eq, Enum, Bounded)
class PrettyPrintable a where
type SymbolTable = Map String SymbolType
-data Quantification =
- Forall |
- Bound
+data Quantification
+ = Forall
+ | Bound
deriving Show
-data SymbolType =
- ValueTag ValueType [IndexType] |
- IndexTag IndexType Quantification
+data SymbolType
+ = ValueTag ValueType [IndexType]
+ | IndexTag IndexType Quantification
deriving Show
-data ValueType =
- ScalarT ScalarType |
- PositionT PositionFieldType |
- MomentumT MomentumFieldType
+data ValueType
+ = ScalarT ScalarType
+ | PositionT PositionFieldType
+ | MomentumT MomentumFieldType
deriving (Eq, Show)
-data ScalarType =
- RealType |
- ComplexType |
- IntegerType
+data ScalarType
+ = RealType
+ | ComplexType
+ | IntegerType
deriving (Eq, Show)
instance Monoid ScalarType where
mappend ComplexType _ = ComplexType
mappend _ ComplexType = ComplexType
-data PositionFieldType =
- Psinc Integer |
- AnalyticPositionType
+data PositionFieldType
+ = Psinc Integer
+ | AnalyticPositionType
deriving (Eq, Show)
-data MomentumFieldType =
- PsincReciprocal Integer |
- AnalyticMomentumType
+data MomentumFieldType
+ = PsincReciprocal Integer
+ | AnalyticMomentumType
deriving (Eq, Show)
data PsincE
deriving instance Show PsincReciprocalE
deriving instance Show ScalarE
-data OperatorExpr num terminal =
- OpAdd (OperatorExpr num terminal) (OperatorExpr num terminal) |
- OpSub (OperatorExpr num terminal) (OperatorExpr num terminal) |
- OpMul (OperatorExpr num terminal) (OperatorExpr num terminal) |
- OpDiv (OperatorExpr num terminal) (OperatorExpr num terminal) |
- OpPow (OperatorExpr num terminal) (OperatorExpr num terminal) |
- OpNeg (OperatorExpr num terminal) |
- OpIndexedScalarIdentifier String [String] |
- OpConstant num |
- OpTerminal terminal
+data OperatorExpr num terminal
+ = OpAdd (OperatorExpr num terminal) (OperatorExpr num terminal)
+ | OpSub (OperatorExpr num terminal) (OperatorExpr num terminal)
+ | OpMul (OperatorExpr num terminal) (OperatorExpr num terminal)
+ | OpDiv (OperatorExpr num terminal) (OperatorExpr num terminal)
+ | OpPow (OperatorExpr num terminal) (OperatorExpr num terminal)
+ | OpNeg (OperatorExpr num terminal)
+ | OpIndexedScalarIdentifier String [String]
+ | OpConstant num
+ | OpTerminal terminal
deriving Show
instance (PrettyPrintable num, PrettyPrintable terminal) => PrettyPrintable (OperatorExpr num terminal) where
where
binaryToDoc op lhs rhs = parens $ hcat [toDoc lhs, text op, toDoc rhs]
-data PositionTerminal =
- PositionComponent String
+data PositionTerminal
+ = PositionComponent String
deriving Show
instance PrettyPrintable PositionTerminal where
toDoc (PositionComponent index) = text $ "r[" ++ index ++ "]"
-data MomentumTerminal =
- MomentumComponent String
+data MomentumTerminal
+ = MomentumComponent String
deriving Show
instance PrettyPrintable MomentumTerminal where
Left _ -> []
Right _ -> resampled ofl2 e
-data Assignment =
- AssignPsinc (Expression PsincE) (Expression PsincE) |
- AssignScalar (Expression ScalarE) (Expression ScalarE)
+data Assignment
+ = AssignPsinc (Expression PsincE) (Expression PsincE)
+ | AssignScalar (Expression ScalarE) (Expression ScalarE)
deriving Show
instance PrettyPrintable Assignment where
-- Frequency fixup
-data Bandwidth =
- GMaxMultiple Integer |
- Infinite
+data Bandwidth
+ = GMaxMultiple Integer
+ | Infinite
deriving (Eq, Show)
instance Ord Bandwidth where
type MappingTable = Map String TargetType
-data TargetType =
- FortranParameter [FortranParamProperty] |
- PPDFunctionSet [PPDFunctionSetProperty]
+data TargetType
+ = FortranParameter [FortranParamProperty]
+ | PPDFunctionSet [PPDFunctionSetProperty]
deriving Show
-data FortranType =
- Array FortranType [ArrayIndex] |
- SPAM3 |
- FunctionBasis |
- Double |
- Integer
+data FortranType
+ = Array FortranType [ArrayIndex]
+ | SPAM3
+ | FunctionBasis
+ | Double
+ | Integer
deriving Show
-data ArrayIndex =
- UnnamedIndex |
- NamedIndex String
+data ArrayIndex
+ = UnnamedIndex
+ | NamedIndex String
deriving Show
-data SpaceInfo =
- CoarsePsinc [String] |
- FinePsinc [String]
+data SpaceInfo
+ = CoarsePsinc [String]
+ | FinePsinc [String]
deriving Show
-data FortranParamProperty =
- ParamName String |
- ParamType FortranType |
- Space SpaceInfo |
- Indexed [String]
+data FortranParamProperty
+ = ParamName String
+ | ParamType FortranType
+ | Space SpaceInfo
+ | Indexed [String]
deriving Show
-data PPDFunctionSetProperty =
- PPDData String |
- PPDBasis String
+data PPDFunctionSetProperty
+ = PPDData String
+ | PPDBasis String
deriving Show
data FortranFunction =
FortranFunction String [FortranFunctionProperty]
deriving Show
-data FortranFunctionProperty =
- FortranFunctionName String |
- FortranFunctionParams [String]
+data FortranFunctionProperty
+ = FortranFunctionName String
+ | FortranFunctionParams [String]
deriving Show
findSpace :: [FortranParamProperty] -> Maybe SpaceInfo
import qualified Data.Set as Set
-- The top-level types
-data BaseType =
- RealType |
- FunctionType |
- IntegerType
+data BaseType
+ = RealType
+ | FunctionType
+ | IntegerType
deriving (Show, Eq, Enum, Bounded)
-data GeneralType =
- FieldType |
- ScalarType
+data GeneralType
+ = FieldType
+ | ScalarType
deriving Show
baseToGeneralType :: BaseType -> GeneralType
baseToGeneralType IntegerType = ScalarType
-- Expressions
-data Expression =
- IndexedIdentifier String [String] |
- ConstReal Double |
- ConstInteger Integer |
- Negate Expression |
- Integrate Expression |
- Sum Expression String |
- Multiply Expression Expression |
- Divide Expression Expression |
- Add Expression Expression |
- Sub Expression Expression |
- Power Expression Expression |
- PositionComponent String |
- SpatialDerivative Expression String Integer
+data Expression
+ = IndexedIdentifier String [String]
+ | ConstReal Double
+ | ConstInteger Integer
+ | Negate Expression
+ | Integrate Expression
+ | Sum Expression String
+ | Multiply Expression Expression
+ | Divide Expression Expression
+ | Add Expression Expression
+ | Sub Expression Expression
+ | Power Expression Expression
+ | PositionComponent String
+ | SpatialDerivative Expression String Integer
deriving Show
instance PrettyPrintable Expression where
binaryToDoc op lhs rhs = parens $ hcat [toDoc lhs, text op, toDoc rhs]
functionToDoc name params = text name <> (parens $ hcat (intersperse (text ", ") params))
-data Assignment =
- Assign Expression Expression
+data Assignment
+ = Assign Expression Expression
deriving Show
instance PrettyPrintable Assignment where
toOFLString indexType = show indexType
-- The symbol table
-data SymbolType =
- ValueTag BaseType [IndexType] |
- IndexTag IndexType
+data SymbolType
+ = ValueTag BaseType [IndexType]
+ | IndexTag IndexType
deriving Show
type SymbolTable = Map String SymbolType
}
-- Validation
-data ValidationError = Message String deriving Show
+data ValidationError
+ = Message String
+ deriving Show
+
type ValidationResult = Either ValidationError ()
validationSuccess :: ValidationResult