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

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

Documentation

data Boz Source #

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

Instances details
Out Boz Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

docPrec :: Int -> Boz -> Doc #

doc :: Boz -> Doc #

docList :: [Boz] -> Doc #

Data Boz Source # 
Instance details

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 #

toConstr :: Boz -> Constr #

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 # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Associated Types

type Rep Boz :: Type -> Type #

Methods

from :: Boz -> Rep Boz x #

to :: Rep Boz x -> Boz #

Show Boz Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

showsPrec :: Int -> Boz -> ShowS #

show :: Boz -> String #

showList :: [Boz] -> ShowS #

NFData Boz Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

rnf :: Boz -> () #

Eq Boz Source #

Tests prefix & strings match, ignoring conforming/nonconforming flags.

Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

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

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

Ord Boz Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

compare :: Boz -> Boz -> Ordering #

(<) :: Boz -> Boz -> Bool #

(<=) :: Boz -> Boz -> Bool #

(>) :: Boz -> Boz -> Bool #

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

max :: Boz -> Boz -> Boz #

min :: Boz -> Boz -> Boz #

type Rep Boz Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

type Rep Boz = D1 ('MetaData "Boz" "Language.Fortran.AST.Literal.Boz" "fortran-src-0.10.1-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))))

data BozPrefix Source #

Constructors

BozPrefixB

binary (bitstring)

BozPrefixO

octal

BozPrefixZ Conforming

hex, including nonstandard x

Instances

Instances details
Out BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

docPrec :: Int -> BozPrefix -> Doc #

doc :: BozPrefix -> Doc #

docList :: [BozPrefix] -> Doc #

Data BozPrefix Source # 
Instance details

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 # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Associated Types

type Rep BozPrefix :: Type -> Type #

Show BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

NFData BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

rnf :: BozPrefix -> () #

Eq BozPrefix Source #

Ignores conforming/nonconforming flags.

Instance details

Defined in Language.Fortran.AST.Literal.Boz

Ord BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

type Rep BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

type Rep BozPrefix = D1 ('MetaData "BozPrefix" "Language.Fortran.AST.Literal.Boz" "fortran-src-0.10.1-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

Instances details
Out Conforming Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Data Conforming Source # 
Instance details

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) -> Conforming -> c Conforming #

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

toConstr :: Conforming -> Constr #

dataTypeOf :: Conforming -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Conforming Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Associated Types

type Rep Conforming :: Type -> Type #

Show Conforming Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

NFData Conforming Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Methods

rnf :: Conforming -> () #

Eq Conforming Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

Ord Conforming Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

type Rep Conforming Source # 
Instance details

Defined in Language.Fortran.AST.Literal.Boz

type Rep Conforming = D1 ('MetaData "Conforming" "Language.Fortran.AST.Literal.Boz" "fortran-src-0.10.1-inplace" 'False) (C1 ('MetaCons "Conforming" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Nonconforming" 'PrefixI 'False) (U1 :: Type -> Type))

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.

bozAsNatural :: (Num a, Eq a) => Boz -> a Source #

Resolve a BOZ constant as a natural (positive integer).

Is actually polymorphic over the output type, but you probably want to resolve to Integer or Natural usually.

We assume the Boz is well-formed, thus don't bother with digit predicates.

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.