Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- data RealLit = RealLit {}
- data Exponent = Exponent {}
- data ExponentLetter
- prettyHsRealLit :: RealLit -> String
- readRealLit :: (Fractional a, Read a) => RealLit -> a
- parseRealLit :: String -> RealLit
Documentation
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
Eq RealLit Source # | |
Data RealLit Source # | |
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 # | |
Defined in Language.Fortran.AST.RealLit | |
Show RealLit Source # | |
Generic RealLit Source # | |
Out RealLit Source # | |
NFData RealLit Source # | |
Defined in Language.Fortran.AST.RealLit | |
type Rep RealLit Source # | |
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))) |
An exponent is an exponent letter (E, D) and a signed integer.
Constructors
Exponent | |
Fields |
Instances
Eq Exponent Source # | |
Data Exponent Source # | |
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 # | |
Defined in Language.Fortran.AST.RealLit | |
Show Exponent Source # | |
Generic Exponent Source # | |
Out Exponent Source # | |
NFData Exponent Source # | |
Defined in Language.Fortran.AST.RealLit | |
type Rep Exponent Source # | |
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
readRealLit :: (Fractional a, Read a) => RealLit -> a Source #
parseRealLit :: String -> RealLit Source #