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

Language.Fortran.AST.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.

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 

Instances

Instances details
Eq Boz Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Methods

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

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

Data Boz Source # 
Instance details

Defined in Language.Fortran.AST.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 #

Ord Boz Source # 
Instance details

Defined in Language.Fortran.AST.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 #

Show Boz Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Methods

showsPrec :: Int -> Boz -> ShowS #

show :: Boz -> String #

showList :: [Boz] -> ShowS #

Generic Boz Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Associated Types

type Rep Boz :: Type -> Type #

Methods

from :: Boz -> Rep Boz x #

to :: Rep Boz x -> Boz #

Out Boz Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Methods

docPrec :: Int -> Boz -> Doc #

doc :: Boz -> Doc #

docList :: [Boz] -> Doc #

NFData Boz Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Methods

rnf :: Boz -> () #

type Rep Boz Source # 
Instance details

Defined in Language.Fortran.AST.Boz

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

data BozPrefix Source #

Constructors

BozPrefixB

binary (bitstring)

BozPrefixO

octal

BozPrefixZ

hex (also with prefix x)

Instances

Instances details
Eq BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Data BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.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 #

Ord BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Show BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Generic BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Associated Types

type Rep BozPrefix :: Type -> Type #

Out BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Methods

docPrec :: Int -> BozPrefix -> Doc #

doc :: BozPrefix -> Doc #

docList :: [BozPrefix] -> Doc #

NFData BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Boz

Methods

rnf :: BozPrefix -> () #

type Rep BozPrefix Source # 
Instance details

Defined in Language.Fortran.AST.Boz

type Rep BozPrefix = D1 ('MetaData "BozPrefix" "Language.Fortran.AST.Boz" "fortran-src-0.9.0-inplace" 'False) (C1 ('MetaCons "BozPrefixB" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BozPrefixO" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BozPrefixZ" 'PrefixI 'False) (U1 :: Type -> Type)))

parseBoz :: String -> Boz Source #

UNSAFE. Parses a BOZ literal constant string.

Looks for prefix or suffix. Strips the quotes from the string (single quotes only).

prettyBoz :: Boz -> String Source #

Pretty print a BOZ constant. Uses prefix style, 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.