hpython-0.3: Python language tools

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

Language.Python.Syntax.Punctuation

Description

These types are used throughout the syntax tree to help preserve formatting.

Synopsis

Documentation

newtype Dot Source #

A period character, possibly followed by some whitespace.

Constructors

MkDot [Whitespace] 
Instances
Eq Dot Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

Show Dot Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

showsPrec :: Int -> Dot -> ShowS #

show :: Dot -> String #

showList :: [Dot] -> ShowS #

HasTrailingWhitespace Dot Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

HasNewlines Dot Source # 
Instance details

Defined in Language.Python.Optics.Newlines

newtype Comma Source #

The venerable comma separator

Constructors

MkComma [Whitespace] 
Instances
Eq Comma Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

Show Comma Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

showsPrec :: Int -> Comma -> ShowS #

show :: Comma -> String #

showList :: [Comma] -> ShowS #

Generic Comma Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Associated Types

type Rep Comma :: Type -> Type #

Methods

from :: Comma -> Rep Comma x #

to :: Rep Comma x -> Comma #

HasTrailingWhitespace Comma Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

HasNewlines Comma Source # 
Instance details

Defined in Language.Python.Optics.Newlines

type Rep Comma Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

type Rep Comma = D1 (MetaData "Comma" "Language.Python.Syntax.Punctuation" "hpython-0.3-inplace" True) (C1 (MetaCons "MkComma" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))

newtype Colon Source #

Constructors

MkColon [Whitespace] 
Instances
Eq Colon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

Show Colon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

showsPrec :: Int -> Colon -> ShowS #

show :: Colon -> String #

showList :: [Colon] -> ShowS #

Generic Colon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Associated Types

type Rep Colon :: Type -> Type #

Methods

from :: Colon -> Rep Colon x #

to :: Rep Colon x -> Colon #

HasTrailingWhitespace Colon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

HasNewlines Colon Source # 
Instance details

Defined in Language.Python.Optics.Newlines

type Rep Colon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

type Rep Colon = D1 (MetaData "Colon" "Language.Python.Syntax.Punctuation" "hpython-0.3-inplace" True) (C1 (MetaCons "MkColon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))

data Semicolon a Source #

Constructors

MkSemicolon (Ann a) [Whitespace] 
Instances
Functor Semicolon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

Foldable Semicolon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

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

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

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

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

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

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

toList :: Semicolon a -> [a] #

null :: Semicolon a -> Bool #

length :: Semicolon a -> Int #

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

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

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

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

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

Traversable Semicolon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

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

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

HasAnn Semicolon Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

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

Defined in Language.Python.Syntax.Punctuation

Generic (Semicolon a) Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Associated Types

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

Methods

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

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

HasTrailingWhitespace (Semicolon a) Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

HasNewlines (Semicolon a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

type Rep (Semicolon a) Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

type Rep (Semicolon a) = D1 (MetaData "Semicolon" "Language.Python.Syntax.Punctuation" "hpython-0.3-inplace" False) (C1 (MetaCons "MkSemicolon" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))

newtype At Source #

Constructors

MkAt [Whitespace] 
Instances
Eq At Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

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

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

Show At Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

Methods

showsPrec :: Int -> At -> ShowS #

show :: At -> String #

showList :: [At] -> ShowS #

HasTrailingWhitespace At Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

HasNewlines At Source # 
Instance details

Defined in Language.Python.Optics.Newlines