Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Language.Fortran.AST.Literal.Boz
Description
Supporting code for handling Fortran BOZ literal constants.
Using the definition from the latest Fortran standards (F2003, F2008), BOZ constants are bitstrings (untyped!) which have basically no implicit rules. How they're interpreted depends on context (they are generally limited to DATA statements and a small handful of intrinsic functions).
Note that currently, we don't store BOZ constants as bitstrings. Storing them in
their string representation is easy and in that form, they're easy to safely
resolve to an integer. An alternate option would be to store them as the
bitstring B of BOZ, and only implement functions on that. For simple uses
(integer), I'm doubtful that would provide extra utility or performance, but it
may be more sensible in the future. For now, you may retrieve a bitstring by
converting to a numeric type and using something like showIntAtBase
, or a
Bits
instance.
This type carries _some_ syntactic information that doesn't change meaning. The
expectation is that most users won't want to inspect Boz
values, usually just
convert them, so we do it for convenience for checking syntax conformance. Note
that not all info is retained -- which of single or double quotes were used is
not recorded, for example.
Synopsis
- data Boz = Boz {}
- data BozPrefix
- data Conforming
- parseBoz :: String -> Boz
- prettyBoz :: Boz -> String
- bozAsNatural :: (Num a, Eq a) => Boz -> a
- bozAsTwosComp :: (Num a, Eq a, FiniteBits a) => Boz -> a
Documentation
A Fortran BOZ literal constant.
The prefix defines the characters allowed in the string:
B
:[01]
O
:[0-7]
Z
:[0-9 a-f A-F]
Constructors
Boz | |
Fields
|
Instances
Out Boz Source # | |
Data Boz Source # | |
Defined in Language.Fortran.AST.Literal.Boz Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boz -> c Boz # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boz # dataTypeOf :: Boz -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Boz) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boz) # gmapT :: (forall b. Data b => b -> b) -> Boz -> Boz # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boz -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boz -> r # gmapQ :: (forall d. Data d => d -> u) -> Boz -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Boz -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boz -> m Boz # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boz -> m Boz # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boz -> m Boz # | |
Generic Boz Source # | |
Show Boz Source # | |
NFData Boz Source # | |
Defined in Language.Fortran.AST.Literal.Boz | |
Eq Boz Source # | Tests prefix & strings match, ignoring conforming/nonconforming flags. |
Ord Boz Source # | |
type Rep Boz Source # | |
Defined in Language.Fortran.AST.Literal.Boz type Rep Boz = D1 ('MetaData "Boz" "Language.Fortran.AST.Literal.Boz" "fortran-src-0.14.0-inplace" 'False) (C1 ('MetaCons "Boz" 'PrefixI 'True) (S1 ('MetaSel ('Just "bozPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BozPrefix) :*: (S1 ('MetaSel ('Just "bozString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "bozPrefixWasPostfix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Conforming)))) |
Constructors
BozPrefixB | binary (bitstring) |
BozPrefixO | octal |
BozPrefixZ Conforming | hex, including nonstandard |
Instances
Out BozPrefix Source # | |
Data BozPrefix Source # | |
Defined in Language.Fortran.AST.Literal.Boz Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BozPrefix -> c BozPrefix # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BozPrefix # toConstr :: BozPrefix -> Constr # dataTypeOf :: BozPrefix -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BozPrefix) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BozPrefix) # gmapT :: (forall b. Data b => b -> b) -> BozPrefix -> BozPrefix # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BozPrefix -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BozPrefix -> r # gmapQ :: (forall d. Data d => d -> u) -> BozPrefix -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BozPrefix -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BozPrefix -> m BozPrefix # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BozPrefix -> m BozPrefix # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BozPrefix -> m BozPrefix # | |
Generic BozPrefix Source # | |
Show BozPrefix Source # | |
NFData BozPrefix Source # | |
Defined in Language.Fortran.AST.Literal.Boz | |
Eq BozPrefix Source # | Ignores conforming/nonconforming flags. |
Ord BozPrefix Source # | |
Defined in Language.Fortran.AST.Literal.Boz | |
type Rep BozPrefix Source # | |
Defined in Language.Fortran.AST.Literal.Boz type Rep BozPrefix = D1 ('MetaData "BozPrefix" "Language.Fortran.AST.Literal.Boz" "fortran-src-0.14.0-inplace" 'False) (C1 ('MetaCons "BozPrefixB" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BozPrefixO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BozPrefixZ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Conforming)))) |
data Conforming Source #
Constructors
Conforming | |
Nonconforming |
Instances
parseBoz :: String -> Boz Source #
UNSAFE. Parses a BOZ literal constant string.
Looks for prefix or postfix. Strips the quotes from the string (single quotes only).
prettyBoz :: Boz -> String Source #
Pretty print a BOZ constant. Uses prefix style (ignores the postfix field),
and z
over nonstandard x
for hexadecimal.
bozAsTwosComp :: (Num a, Eq a, FiniteBits a) => Boz -> a Source #
Resolve a BOZ constant as a two's complement integer.
Note that the value will depend on the size of the output type.