fortran-src-0.15.0: Parsers and analyses for Fortran standards 66, 77, 90, 95 and 2003 (partial).
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Fortran.Repr.Eval.Value

Description

Evaluate AST terms to values in the value representation.

Synopsis

Documentation

data Error Source #

Error encountered while evaluating a Fortran expression to a value.

Constructors

ENoSuchVar Name 
EKindLitBadType Name FType 
ENoSuchKindForType String FKindLit 
EUnsupported String

Syntax which probably should be supported, but (currently) isn't.

EOp Error 
EOpTypeError String 
ESpecial String

Special value-like expression that we can't evaluate usefully.

ELazy String

Catch-all for non-grouped errors.

Instances

Instances details
Generic Error Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

Show Error Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Eq Error Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

MonadError Error FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

type Rep Error Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

type Rep Error = D1 ('MetaData "Error" "Language.Fortran.Repr.Eval.Value" "fortran-src-0.15.0-inplace" 'False) (((C1 ('MetaCons "ENoSuchVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "EKindLitBadType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FType))) :+: (C1 ('MetaCons "ENoSuchKindForType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FKindLit)) :+: C1 ('MetaCons "EUnsupported" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "EOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Error)) :+: C1 ('MetaCons "EOpTypeError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "ESpecial" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ELazy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

type MonadFEvalValue m = (MonadFEval m, EvalTo m ~ FValue, MonadError Error m) Source #

A convenience constraint tuple defining the base requirements of the FValue evaluator.

The evaluator is formed of combinators returning values in this monad. You may insert your own evaluator which handles monadic actions differently, provided it can fulfill these constraints.

newtype FEvalValuePure a Source #

A simple pure interpreter for Fortran value evaluation programs.

Instances

Instances details
Applicative FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

Functor FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

Methods

fmap :: (a -> b) -> FEvalValuePure a -> FEvalValuePure b #

(<$) :: a -> FEvalValuePure b -> FEvalValuePure a #

Monad FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

MonadFEval FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

Associated Types

type EvalTo FEvalValuePure Source #

MonadError Error FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

MonadWriter [String] FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

MonadReader (Map Name FValue) FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

type EvalTo FEvalValuePure Source # 
Instance details

Defined in Language.Fortran.Repr.Eval.Value

err :: MonadError Error m => Error -> m a Source #

wrapSOp :: MonadFEvalValue m => Either Error FScalarValue -> m FValue Source #

Wrap the output of an operation that returns a scalar value into the main evaluator.

evalBOp :: MonadFEvalValue m => BinaryOp -> FValue -> FValue -> m FValue Source #

Evaluate explicit binary operators (ones denoted as such in the AST).

Note that this does not cover all binary operators -- there are many intrinsics which use function syntax, but are otherwise binary operators.

evalIntrinsicInt4 :: MonadFEvalValue m => FValue -> m Int32 Source #

INT(a, 4), INT(a)

evalIntrinsicIntXCoerce :: forall r m. (MonadFEvalValue m, Integral r) => (FInt -> r) -> FValue -> m r Source #

forceUnconsArg :: MonadFEvalValue m => [a] -> m (a, [a]) Source #

forceArgs :: MonadFEvalValue m => Int -> [a] -> m [a] Source #

evalConstExpr :: MonadFEvalValue m => Expression a -> m FValue Source #

Evaluate a constant expression (F2018 10.1.12).