hpython-0.2: Python language tools

Copyright(C) CSIRO 2017-2019
LicenseBSD3
MaintainerIsaac Elliott <isaace71295@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Language.Python.Syntax.Numbers

Contents

Description

Numerical literal values in Python

Synopsis

Datatypes

data IntLiteral a Source #

An integer literal value.

5 is an integer literal.

6.2 is a literal but is not an integer

x might be an integer, but is not a literal

See https://docs.python.org/3.5/reference/lexical_analysis.html#integer-literals

Instances
Functor IntLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

fmap :: (a -> b) -> IntLiteral a -> IntLiteral b #

(<$) :: a -> IntLiteral b -> IntLiteral a #

Foldable IntLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

fold :: Monoid m => IntLiteral m -> m #

foldMap :: Monoid m => (a -> m) -> IntLiteral a -> m #

foldr :: (a -> b -> b) -> b -> IntLiteral a -> b #

foldr' :: (a -> b -> b) -> b -> IntLiteral a -> b #

foldl :: (b -> a -> b) -> b -> IntLiteral a -> b #

foldl' :: (b -> a -> b) -> b -> IntLiteral a -> b #

foldr1 :: (a -> a -> a) -> IntLiteral a -> a #

foldl1 :: (a -> a -> a) -> IntLiteral a -> a #

toList :: IntLiteral a -> [a] #

null :: IntLiteral a -> Bool #

length :: IntLiteral a -> Int #

elem :: Eq a => a -> IntLiteral a -> Bool #

maximum :: Ord a => IntLiteral a -> a #

minimum :: Ord a => IntLiteral a -> a #

sum :: Num a => IntLiteral a -> a #

product :: Num a => IntLiteral a -> a #

Traversable IntLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

traverse :: Applicative f => (a -> f b) -> IntLiteral a -> f (IntLiteral b) #

sequenceA :: Applicative f => IntLiteral (f a) -> f (IntLiteral a) #

mapM :: Monad m => (a -> m b) -> IntLiteral a -> m (IntLiteral b) #

sequence :: Monad m => IntLiteral (m a) -> m (IntLiteral a) #

Eq1 IntLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

liftEq :: (a -> b -> Bool) -> IntLiteral a -> IntLiteral b -> Bool #

Ord1 IntLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

liftCompare :: (a -> b -> Ordering) -> IntLiteral a -> IntLiteral b -> Ordering #

HasAnn IntLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

annot :: Lens' (IntLiteral a) (Ann a) Source #

Eq a => Eq (IntLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

(==) :: IntLiteral a -> IntLiteral a -> Bool #

(/=) :: IntLiteral a -> IntLiteral a -> Bool #

Show a => Show (IntLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Generic (IntLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Associated Types

type Rep (IntLiteral a) :: Type -> Type #

Methods

from :: IntLiteral a -> Rep (IntLiteral a) x #

to :: Rep (IntLiteral a) x -> IntLiteral a #

type Rep (IntLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

type Rep (IntLiteral a) = D1 (MetaData "IntLiteral" "Language.Python.Syntax.Numbers" "hpython-0.2-7fNN6PEHntyHCqZaN2NGK0" False) ((C1 (MetaCons "IntLiteralDec" PrefixI True) (S1 (MetaSel (Just "_intLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: S1 (MetaSel (Just "_unsafeIntLiteralDecValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty DecDigit))) :+: C1 (MetaCons "IntLiteralBin" PrefixI True) (S1 (MetaSel (Just "_intLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeIntLiteralBinUppercase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "_unsafeIntLiteralBinValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty BinDigit))))) :+: (C1 (MetaCons "IntLiteralOct" PrefixI True) (S1 (MetaSel (Just "_intLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeIntLiteralOctUppercase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "_unsafeIntLiteralOctValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty OctDigit)))) :+: C1 (MetaCons "IntLiteralHex" PrefixI True) (S1 (MetaSel (Just "_intLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeIntLiteralHexUppercase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "_unsafeIntLiteralHexValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty HeXDigit))))))

data Sign Source #

Positive or negative, as in -7

Constructors

Pos 
Neg 
Instances
Eq Sign Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

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

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

Ord Sign Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

compare :: Sign -> Sign -> Ordering #

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

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

(>) :: Sign -> Sign -> Bool #

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

max :: Sign -> Sign -> Sign #

min :: Sign -> Sign -> Sign #

Show Sign Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

Generic Sign Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Associated Types

type Rep Sign :: Type -> Type #

Methods

from :: Sign -> Rep Sign x #

to :: Rep Sign x -> Sign #

type Rep Sign Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

type Rep Sign = D1 (MetaData "Sign" "Language.Python.Syntax.Numbers" "hpython-0.2-7fNN6PEHntyHCqZaN2NGK0" False) (C1 (MetaCons "Pos" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Neg" PrefixI False) (U1 :: Type -> Type))

data E Source #

When a floating point literal is in scientific notation, it includes the character e, which can be lower or upper case.

Constructors

Ee 
EE 
Instances
Eq E Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

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

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

Ord E Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

compare :: E -> E -> Ordering #

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

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

(>) :: E -> E -> Bool #

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

max :: E -> E -> E #

min :: E -> E -> E #

Show E Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

showsPrec :: Int -> E -> ShowS #

show :: E -> String #

showList :: [E] -> ShowS #

Generic E Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Associated Types

type Rep E :: Type -> Type #

Methods

from :: E -> Rep E x #

to :: Rep E x -> E #

type Rep E Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

type Rep E = D1 (MetaData "E" "Language.Python.Syntax.Numbers" "hpython-0.2-7fNN6PEHntyHCqZaN2NGK0" False) (C1 (MetaCons "Ee" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EE" PrefixI False) (U1 :: Type -> Type))

data FloatExponent Source #

The exponent of a floating point literal.

An e, followed by an optional Sign, followed by at least one digit.

Instances
Eq FloatExponent Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Ord FloatExponent Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Show FloatExponent Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Generic FloatExponent Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Associated Types

type Rep FloatExponent :: Type -> Type #

type Rep FloatExponent Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

data FloatLiteral a Source #

Instances
Functor FloatLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

fmap :: (a -> b) -> FloatLiteral a -> FloatLiteral b #

(<$) :: a -> FloatLiteral b -> FloatLiteral a #

Foldable FloatLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

fold :: Monoid m => FloatLiteral m -> m #

foldMap :: Monoid m => (a -> m) -> FloatLiteral a -> m #

foldr :: (a -> b -> b) -> b -> FloatLiteral a -> b #

foldr' :: (a -> b -> b) -> b -> FloatLiteral a -> b #

foldl :: (b -> a -> b) -> b -> FloatLiteral a -> b #

foldl' :: (b -> a -> b) -> b -> FloatLiteral a -> b #

foldr1 :: (a -> a -> a) -> FloatLiteral a -> a #

foldl1 :: (a -> a -> a) -> FloatLiteral a -> a #

toList :: FloatLiteral a -> [a] #

null :: FloatLiteral a -> Bool #

length :: FloatLiteral a -> Int #

elem :: Eq a => a -> FloatLiteral a -> Bool #

maximum :: Ord a => FloatLiteral a -> a #

minimum :: Ord a => FloatLiteral a -> a #

sum :: Num a => FloatLiteral a -> a #

product :: Num a => FloatLiteral a -> a #

Traversable FloatLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

traverse :: Applicative f => (a -> f b) -> FloatLiteral a -> f (FloatLiteral b) #

sequenceA :: Applicative f => FloatLiteral (f a) -> f (FloatLiteral a) #

mapM :: Monad m => (a -> m b) -> FloatLiteral a -> m (FloatLiteral b) #

sequence :: Monad m => FloatLiteral (m a) -> m (FloatLiteral a) #

Eq1 FloatLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

liftEq :: (a -> b -> Bool) -> FloatLiteral a -> FloatLiteral b -> Bool #

Ord1 FloatLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

liftCompare :: (a -> b -> Ordering) -> FloatLiteral a -> FloatLiteral b -> Ordering #

HasAnn FloatLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

annot :: Lens' (FloatLiteral a) (Ann a) Source #

Eq a => Eq (FloatLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Show a => Show (FloatLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Generic (FloatLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Associated Types

type Rep (FloatLiteral a) :: Type -> Type #

Methods

from :: FloatLiteral a -> Rep (FloatLiteral a) x #

to :: Rep (FloatLiteral a) x -> FloatLiteral a #

type Rep (FloatLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

type Rep (FloatLiteral a) = D1 (MetaData "FloatLiteral" "Language.Python.Syntax.Numbers" "hpython-0.2-7fNN6PEHntyHCqZaN2NGK0" False) (C1 (MetaCons "FloatLiteralFull" PrefixI True) (S1 (MetaSel (Just "_floatLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_floatLiteralFullLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty DecDigit)) :*: S1 (MetaSel (Just "_floatLiteralFullRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (These (NonEmpty DecDigit) FloatExponent))))) :+: (C1 (MetaCons "FloatLiteralPoint" PrefixI True) (S1 (MetaSel (Just "_floatLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_floatLiteralPointRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty DecDigit)) :*: S1 (MetaSel (Just "_floatLiteralPointExponent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FloatExponent)))) :+: C1 (MetaCons "FloatLiteralWhole" PrefixI True) (S1 (MetaSel (Just "_floatLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_floatLiteralWholeRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty DecDigit)) :*: S1 (MetaSel (Just "_floatLiteralWholeExponent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FloatExponent)))))

data ImagLiteral a Source #

Constructors

ImagLiteralInt

A decimal integer followed by a 'j'

12j
ImagLiteralFloat

A float followed by a 'j'

12.j
12.3j
.3j
Instances
Functor ImagLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

fmap :: (a -> b) -> ImagLiteral a -> ImagLiteral b #

(<$) :: a -> ImagLiteral b -> ImagLiteral a #

Foldable ImagLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

fold :: Monoid m => ImagLiteral m -> m #

foldMap :: Monoid m => (a -> m) -> ImagLiteral a -> m #

foldr :: (a -> b -> b) -> b -> ImagLiteral a -> b #

foldr' :: (a -> b -> b) -> b -> ImagLiteral a -> b #

foldl :: (b -> a -> b) -> b -> ImagLiteral a -> b #

foldl' :: (b -> a -> b) -> b -> ImagLiteral a -> b #

foldr1 :: (a -> a -> a) -> ImagLiteral a -> a #

foldl1 :: (a -> a -> a) -> ImagLiteral a -> a #

toList :: ImagLiteral a -> [a] #

null :: ImagLiteral a -> Bool #

length :: ImagLiteral a -> Int #

elem :: Eq a => a -> ImagLiteral a -> Bool #

maximum :: Ord a => ImagLiteral a -> a #

minimum :: Ord a => ImagLiteral a -> a #

sum :: Num a => ImagLiteral a -> a #

product :: Num a => ImagLiteral a -> a #

Traversable ImagLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

traverse :: Applicative f => (a -> f b) -> ImagLiteral a -> f (ImagLiteral b) #

sequenceA :: Applicative f => ImagLiteral (f a) -> f (ImagLiteral a) #

mapM :: Monad m => (a -> m b) -> ImagLiteral a -> m (ImagLiteral b) #

sequence :: Monad m => ImagLiteral (m a) -> m (ImagLiteral a) #

Eq1 ImagLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

liftEq :: (a -> b -> Bool) -> ImagLiteral a -> ImagLiteral b -> Bool #

Ord1 ImagLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

liftCompare :: (a -> b -> Ordering) -> ImagLiteral a -> ImagLiteral b -> Ordering #

HasAnn ImagLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Methods

annot :: Lens' (ImagLiteral a) (Ann a) Source #

Eq a => Eq (ImagLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Show a => Show (ImagLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Generic (ImagLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

Associated Types

type Rep (ImagLiteral a) :: Type -> Type #

Methods

from :: ImagLiteral a -> Rep (ImagLiteral a) x #

to :: Rep (ImagLiteral a) x -> ImagLiteral a #

type Rep (ImagLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Numbers

type Rep (ImagLiteral a) = D1 (MetaData "ImagLiteral" "Language.Python.Syntax.Numbers" "hpython-0.2-7fNN6PEHntyHCqZaN2NGK0" False) (C1 (MetaCons "ImagLiteralInt" PrefixI True) (S1 (MetaSel (Just "_imagLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeImagLiteralIntValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty DecDigit)) :*: S1 (MetaSel (Just "_imagLiteralUppercase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) :+: C1 (MetaCons "ImagLiteralFloat" PrefixI True) (S1 (MetaSel (Just "_imagLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeImagLiteralFloatValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (FloatLiteral a)) :*: S1 (MetaSel (Just "_imagLiteralUppercase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

Rendering

The output of these functions is guaranteed to be valid Python code