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

Language.Fortran.AST.RealLit

Description

Supporting code for handling Fortran REAL literals.

Fortran REAL literals have some idiosyncrasies that prevent them from lining up with Haskell's reals immediately. So, we parse into an intermediate data type that can be easily exported with full precision later. Things we do:

  • Strip explicit positive signs so that signed values either begin with the minus sign - or no sign. (Read doesn't allow explicit positive signs.)
  • Make exponent explicit by adding the default exponent E0 if not present.
  • Make implicit zeroes explicit. .123 -> 0.123, 123. -> 123.0. (Again, Haskell literals do not support this.)
Synopsis

Documentation

data RealLit Source #

A Fortran real literal. (Does not include the optional kind parameter.)

A real literal is formed of a signed rational significand, and an Exponent.

See F90 ISO spec pg.27 / R412-416.

Note that we support signed real literals, even though the F90 spec indicates non-signed real literals are the "default" (signed are only used in a "spare" rule). Our parsers should parse explicit signs as unary operators. There's no harm in supporting signed literals though, especially since the exponent *is* signed.

Constructors

RealLit 

Fields

Instances

Instances details
Eq RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

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

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

Data RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RealLit -> c RealLit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RealLit #

toConstr :: RealLit -> Constr #

dataTypeOf :: RealLit -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RealLit) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RealLit) #

gmapT :: (forall b. Data b => b -> b) -> RealLit -> RealLit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RealLit -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RealLit -> r #

gmapQ :: (forall d. Data d => d -> u) -> RealLit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RealLit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RealLit -> m RealLit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RealLit -> m RealLit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RealLit -> m RealLit #

Ord RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Show RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Generic RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Associated Types

type Rep RealLit :: Type -> Type #

Methods

from :: RealLit -> Rep RealLit x #

to :: Rep RealLit x -> RealLit #

Out RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

docPrec :: Int -> RealLit -> Doc #

doc :: RealLit -> Doc #

docList :: [RealLit] -> Doc #

NFData RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

rnf :: RealLit -> () #

type Rep RealLit Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

type Rep RealLit = D1 ('MetaData "RealLit" "Language.Fortran.AST.RealLit" "fortran-src-0.8.0-inplace" 'False) (C1 ('MetaCons "RealLit" 'PrefixI 'True) (S1 ('MetaSel ('Just "realLitSignificand") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "realLitExponent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exponent)))

data Exponent Source #

An exponent is an exponent letter (E, D) and a signed integer.

Instances

Instances details
Eq Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Data Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exponent -> c Exponent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exponent #

toConstr :: Exponent -> Constr #

dataTypeOf :: Exponent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exponent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exponent) #

gmapT :: (forall b. Data b => b -> b) -> Exponent -> Exponent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exponent -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exponent -> r #

gmapQ :: (forall d. Data d => d -> u) -> Exponent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Exponent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exponent -> m Exponent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exponent -> m Exponent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exponent -> m Exponent #

Ord Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Show Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Generic Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Associated Types

type Rep Exponent :: Type -> Type #

Methods

from :: Exponent -> Rep Exponent x #

to :: Rep Exponent x -> Exponent #

Out Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

docPrec :: Int -> Exponent -> Doc #

doc :: Exponent -> Doc #

docList :: [Exponent] -> Doc #

NFData Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

rnf :: Exponent -> () #

type Rep Exponent Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

type Rep Exponent = D1 ('MetaData "Exponent" "Language.Fortran.AST.RealLit" "fortran-src-0.8.0-inplace" 'False) (C1 ('MetaCons "Exponent" 'PrefixI 'True) (S1 ('MetaSel ('Just "exponentLetter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ExponentLetter) :*: S1 ('MetaSel ('Just "exponentNum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data ExponentLetter Source #

Constructors

ExpLetterE

KIND=4 (float)

ExpLetterD

KIND=8 (double)

ExpLetterQ

KIND=16 ("quad", rare? extension)

Instances

Instances details
Eq ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Data ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExponentLetter -> c ExponentLetter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExponentLetter #

toConstr :: ExponentLetter -> Constr #

dataTypeOf :: ExponentLetter -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExponentLetter) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExponentLetter) #

gmapT :: (forall b. Data b => b -> b) -> ExponentLetter -> ExponentLetter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExponentLetter -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExponentLetter -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExponentLetter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExponentLetter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExponentLetter -> m ExponentLetter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExponentLetter -> m ExponentLetter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExponentLetter -> m ExponentLetter #

Ord ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Show ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Generic ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Associated Types

type Rep ExponentLetter :: Type -> Type #

Out ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

NFData ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

Methods

rnf :: ExponentLetter -> () #

type Rep ExponentLetter Source # 
Instance details

Defined in Language.Fortran.AST.RealLit

type Rep ExponentLetter = D1 ('MetaData "ExponentLetter" "Language.Fortran.AST.RealLit" "fortran-src-0.8.0-inplace" 'False) (C1 ('MetaCons "ExpLetterE" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ExpLetterD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExpLetterQ" 'PrefixI 'False) (U1 :: Type -> Type)))

prettyHsRealLit :: RealLit -> String Source #

Prettify a RealLit in a Haskell-compatible way.