Safe Haskell | None |
---|---|
Language | Haskell98 |
- data UnitInfo
- type EqualityConstrained = Bool
- data Solver
- data AssumeLiterals
- data UnitConstant
- newtype VarCol = VarCol Col
- newtype VarBinder = VarBinder (Name, SrcSpan)
- type VarColEnv = [(VarBinder, (VarCol, [VarCol]))]
- data UnitVarCategory
- type DerivedUnitEnv = [(Name, UnitConstant)]
- type ProcedureNames = (String, Maybe Name, [Name])
- type Procedure = (Maybe VarCol, [VarCol])
- type ProcedureEnv = [(String, Procedure)]
- type LinearSystem = (Matrix Rational, [UnitConstant])
- type Row = Int
- type Col = Int
- type DebugInfo = [(Col, (SrcSpan, String))]
- data UnitAnnotation a = UnitAnnotation {
- prevAnnotation :: a
- unitSpec :: Maybe UnitStatement
- unitInfo :: Maybe UnitInfo
- unitBlock :: Maybe (Block (Analysis (UnitAnnotation a)))
- dbgUnitAnnotation :: UnitAnnotation t -> [Char]
- mkUnitAnnotation :: a -> UnitAnnotation a
- data UnitEnv = UnitEnv {
- _report :: [String]
- _varColEnv :: VarColEnv
- _derivedUnitEnv :: DerivedUnitEnv
- _procedureEnv :: ProcedureEnv
- _calls :: ProcedureEnv
- _unitVarCats :: [UnitVarCategory]
- _reorderedCols :: [Int]
- _underdeterminedCols :: [Int]
- _linearSystem :: LinearSystem
- _debugInfo :: DebugInfo
- _tmpRowsAdded :: [Int]
- _tmpColsAdded :: [Int]
- _success :: Bool
- _evUnitsAdded :: (Int, [String])
- _evCriticals :: [Int]
- _puname :: Maybe ProgramUnitName
- _hasDeclaration :: [Name]
- emptyUnitEnv :: UnitEnv
- varColEnv :: forall cat. ArrowApply cat => Lens cat UnitEnv VarColEnv
- unitVarCats :: forall cat. ArrowApply cat => Lens cat UnitEnv [UnitVarCategory]
- underdeterminedCols :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int]
- tmpRowsAdded :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int]
- tmpColsAdded :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int]
- success :: forall cat. ArrowApply cat => Lens cat UnitEnv Bool
- report :: forall cat. ArrowApply cat => Lens cat UnitEnv [String]
- reorderedCols :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int]
- puname :: forall cat. ArrowApply cat => Lens cat UnitEnv (Maybe ProgramUnitName)
- procedureEnv :: forall cat. ArrowApply cat => Lens cat UnitEnv ProcedureEnv
- linearSystem :: forall cat. ArrowApply cat => Lens cat UnitEnv LinearSystem
- hasDeclaration :: forall cat. ArrowApply cat => Lens cat UnitEnv [Name]
- evUnitsAdded :: forall cat. ArrowApply cat => Lens cat UnitEnv (Int, [String])
- evCriticals :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int]
- derivedUnitEnv :: forall cat. ArrowApply cat => Lens cat UnitEnv DerivedUnitEnv
- debugInfo :: forall cat. ArrowApply cat => Lens cat UnitEnv DebugInfo
- calls :: forall cat. ArrowApply cat => Lens cat UnitEnv ProcedureEnv
- unitMult :: UnitConstant -> UnitConstant -> UnitConstant
- unitScalarMult :: Rational -> UnitConstant -> UnitConstant
- convertUnit :: UnitInfo -> State UnitEnv UnitConstant
- toUnitInfo :: UnitOfMeasure -> UnitInfo
- (<<) :: MonadState f m => Lens (->) f [o] -> o -> m ()
- (<<++) :: MonadState f m => Lens (->) f [a] -> a -> m ()
- addCol :: UnitVarCategory -> State UnitEnv Int
- addRow :: State UnitEnv Int
- addRow' :: UnitConstant -> State UnitEnv Int
- liftUnitEnv :: (Matrix Rational -> Matrix Rational) -> UnitEnv -> UnitEnv
- resetTemps :: State UnitEnv ()
- lookupCaseInsensitive :: String -> [(String, a)] -> Maybe a
- lookupWithoutSrcSpan :: Name -> [(VarBinder, a)] -> Maybe a
- lookupWithSrcSpan :: Name -> SrcSpan -> [(VarBinder, a)] -> Maybe a
- trim :: [(t, Rational)] -> [(t, Rational)]
- data Consistency a
- = Ok a
- | Bad a Int (UnitConstant, [Rational])
- efmap :: (a -> a) -> Consistency a -> Consistency a
- ifDebug :: (?debug :: Bool, Monad m) => m a -> m ()
Documentation
type EqualityConstrained = Bool Source #
data AssumeLiterals Source #
data UnitConstant Source #
VarBinder (Name, SrcSpan) |
data UnitVarCategory Source #
type DerivedUnitEnv = [(Name, UnitConstant)] Source #
type ProcedureNames = (String, Maybe Name, [Name]) Source #
type ProcedureEnv = [(String, Procedure)] Source #
type LinearSystem = (Matrix Rational, [UnitConstant]) Source #
data UnitAnnotation a Source #
UnitAnnotation | |
|
Data a => Data (UnitAnnotation a) Source # | |
Show a => Show (UnitAnnotation a) Source # | |
dbgUnitAnnotation :: UnitAnnotation t -> [Char] Source #
mkUnitAnnotation :: a -> UnitAnnotation a Source #
UnitEnv | |
|
unitVarCats :: forall cat. ArrowApply cat => Lens cat UnitEnv [UnitVarCategory] Source #
underdeterminedCols :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int] Source #
tmpRowsAdded :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int] Source #
tmpColsAdded :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int] Source #
reorderedCols :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int] Source #
procedureEnv :: forall cat. ArrowApply cat => Lens cat UnitEnv ProcedureEnv Source #
linearSystem :: forall cat. ArrowApply cat => Lens cat UnitEnv LinearSystem Source #
hasDeclaration :: forall cat. ArrowApply cat => Lens cat UnitEnv [Name] Source #
evUnitsAdded :: forall cat. ArrowApply cat => Lens cat UnitEnv (Int, [String]) Source #
evCriticals :: forall cat. ArrowApply cat => Lens cat UnitEnv [Int] Source #
derivedUnitEnv :: forall cat. ArrowApply cat => Lens cat UnitEnv DerivedUnitEnv Source #
calls :: forall cat. ArrowApply cat => Lens cat UnitEnv ProcedureEnv Source #
unitMult :: UnitConstant -> UnitConstant -> UnitConstant Source #
unitScalarMult :: Rational -> UnitConstant -> UnitConstant Source #
toUnitInfo :: UnitOfMeasure -> UnitInfo Source #
(<<) :: MonadState f m => Lens (->) f [o] -> o -> m () infix 2 Source #
(<<++) :: MonadState f m => Lens (->) f [a] -> a -> m () infix 2 Source #
Operations on unit environments
resetTemps :: State UnitEnv () Source #
lookupWithoutSrcSpan :: Name -> [(VarBinder, a)] -> Maybe a Source #
lookupWithSrcSpan :: Name -> SrcSpan -> [(VarBinder, a)] -> Maybe a Source #
data Consistency a Source #
Ok a | |
Bad a Int (UnitConstant, [Rational]) |
Show a => Show (Consistency a) Source # | |
efmap :: (a -> a) -> Consistency a -> Consistency a Source #