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.Strings

Contents

Description

Synopsis

Datatypes

Characters

data PyChar Source #

A character in a string literal. This is a large sum type, with a catch-all of a Haskell Char.

Instances
Eq PyChar Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Methods

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

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

Ord PyChar Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Show PyChar Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Generic PyChar Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Associated Types

type Rep PyChar :: Type -> Type #

Methods

from :: PyChar -> Rep PyChar x #

to :: Rep PyChar x -> PyChar #

type Rep PyChar Source # 
Instance details

Defined in Language.Python.Syntax.Strings

type Rep PyChar = D1 (MetaData "PyChar" "Language.Python.Syntax.Strings" "hpython-0.3-inplace" False) ((((C1 (MetaCons "Char_newline" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char_octal1" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OctDigit))) :+: (C1 (MetaCons "Char_octal2" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OctDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OctDigit)) :+: C1 (MetaCons "Char_octal3" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OctDigit) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OctDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OctDigit))))) :+: ((C1 (MetaCons "Char_hex" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit)) :+: C1 (MetaCons "Char_uni16" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit)))) :+: (C1 (MetaCons "Char_uni32" PrefixI False) (((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit))) :*: ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeXDigit)))) :+: (C1 (MetaCons "Char_esc_bslash" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char_esc_singlequote" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "Char_esc_doublequote" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char_esc_a" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Char_esc_b" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char_esc_f" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Char_esc_n" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char_esc_r" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Char_esc_t" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Char_esc_v" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char_lit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char)))))))

fromHaskellString :: String -> [PyChar] Source #

Convert a Haskell string to a list of PyChar. This is useful when writing Python in Haskell.

String information

data QuoteType Source #

Double or single quotation marks?

"Double quotes"
"""Double quotes"""
'Single quotes'
'''Single quotes'''

Constructors

SingleQuote 
DoubleQuote 
Instances
Eq QuoteType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Ord QuoteType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Show QuoteType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Generic QuoteType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Associated Types

type Rep QuoteType :: Type -> Type #

type Rep QuoteType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

type Rep QuoteType = D1 (MetaData "QuoteType" "Language.Python.Syntax.Strings" "hpython-0.3-inplace" False) (C1 (MetaCons "SingleQuote" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DoubleQuote" PrefixI False) (U1 :: Type -> Type))

data StringType Source #

Three pairs of quotations or one?

"""Long string"""
'''Also long string'''
"Short string"
'Also short string'

Constructors

ShortString 
LongString 
Instances
Eq StringType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Ord StringType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Show StringType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Generic StringType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Associated Types

type Rep StringType :: Type -> Type #

type Rep StringType Source # 
Instance details

Defined in Language.Python.Syntax.Strings

type Rep StringType = D1 (MetaData "StringType" "Language.Python.Syntax.Strings" "hpython-0.3-inplace" False) (C1 (MetaCons "ShortString" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LongString" PrefixI False) (U1 :: Type -> Type))

String prefixes

data StringPrefix Source #

In Python 3.5, a prefix of u or U is allowed, but doesn't have any meaning. They exist for backwards compatibility with Python 2.

See https://www.python.org/dev/peps/pep-0414/

Constructors

Prefix_u 
Prefix_U 

data RawStringPrefix Source #

Raw strings are prefixed with either r or R.

Constructors

Prefix_r 
Prefix_R 
Instances
Eq RawStringPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Ord RawStringPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Show RawStringPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Generic RawStringPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Associated Types

type Rep RawStringPrefix :: Type -> Type #

type Rep RawStringPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

type Rep RawStringPrefix = D1 (MetaData "RawStringPrefix" "Language.Python.Syntax.Strings" "hpython-0.3-inplace" False) (C1 (MetaCons "Prefix_r" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Prefix_R" PrefixI False) (U1 :: Type -> Type))

data BytesPrefix Source #

This prefix indicates it's a bytes literal rather than a string literal.

Constructors

Prefix_b 
Prefix_B 
Instances
Eq BytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Ord BytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Show BytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Generic BytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Associated Types

type Rep BytesPrefix :: Type -> Type #

type Rep BytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

type Rep BytesPrefix = D1 (MetaData "BytesPrefix" "Language.Python.Syntax.Strings" "hpython-0.3-inplace" False) (C1 (MetaCons "Prefix_b" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Prefix_B" PrefixI False) (U1 :: Type -> Type))

data RawBytesPrefix Source #

A string of raw bytes can be indicated by a number of prefixes

Instances
Eq RawBytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Ord RawBytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Show RawBytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Generic RawBytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Associated Types

type Rep RawBytesPrefix :: Type -> Type #

type Rep RawBytesPrefix Source # 
Instance details

Defined in Language.Python.Syntax.Strings

type Rep RawBytesPrefix = D1 (MetaData "RawBytesPrefix" "Language.Python.Syntax.Strings" "hpython-0.3-inplace" False) (((C1 (MetaCons "Prefix_br" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Prefix_Br" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Prefix_bR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Prefix_BR" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Prefix_rb" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Prefix_rB" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Prefix_Rb" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Prefix_RB" PrefixI False) (U1 :: Type -> Type))))

hasPrefix :: StringLiteral a -> Bool Source #

Most types of StringLiteral have prefixes. Plain old strings may have an optional prefix, but it is meaningless.

String literals

data StringLiteral a Source #

A StringLiteral, complete with a prefix, information about quote type and number, and a list of PyChars.

Like many other data types in hpython, it has an annotation and trailing whitespace.

Instances
Functor StringLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Methods

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

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

Foldable StringLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Methods

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

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

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

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

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

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

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

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

toList :: StringLiteral a -> [a] #

null :: StringLiteral a -> Bool #

length :: StringLiteral a -> Int #

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

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

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

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

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

Traversable StringLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Methods

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

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

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

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

HasAnn StringLiteral Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Methods

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

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

Defined in Language.Python.Syntax.Strings

Ord a => Ord (StringLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Strings

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

Defined in Language.Python.Syntax.Strings

Generic (StringLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Strings

Associated Types

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

HasTrailingWhitespace (StringLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Strings

HasNewlines (StringLiteral a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

type Rep (StringLiteral a) Source # 
Instance details

Defined in Language.Python.Syntax.Strings

type Rep (StringLiteral a) = D1 (MetaData "StringLiteral" "Language.Python.Syntax.Strings" "hpython-0.3-inplace" False) ((C1 (MetaCons "RawStringLiteral" PrefixI True) ((S1 (MetaSel (Just "_stringLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeRawStringLiteralPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RawStringPrefix) :*: S1 (MetaSel (Just "_stringLiteralStringType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StringType))) :*: (S1 (MetaSel (Just "_stringLiteralQuoteType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QuoteType) :*: (S1 (MetaSel (Just "_stringLiteralValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PyChar]) :*: S1 (MetaSel (Just "_stringLiteralWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))) :+: C1 (MetaCons "StringLiteral" PrefixI True) ((S1 (MetaSel (Just "_stringLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeStringLiteralPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe StringPrefix)) :*: S1 (MetaSel (Just "_stringLiteralStringType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StringType))) :*: (S1 (MetaSel (Just "_stringLiteralQuoteType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QuoteType) :*: (S1 (MetaSel (Just "_stringLiteralValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PyChar]) :*: S1 (MetaSel (Just "_stringLiteralWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))))) :+: (C1 (MetaCons "RawBytesLiteral" PrefixI True) ((S1 (MetaSel (Just "_stringLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeRawBytesLiteralPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RawBytesPrefix) :*: S1 (MetaSel (Just "_stringLiteralStringType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StringType))) :*: (S1 (MetaSel (Just "_stringLiteralQuoteType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QuoteType) :*: (S1 (MetaSel (Just "_stringLiteralValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PyChar]) :*: S1 (MetaSel (Just "_stringLiteralWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace])))) :+: C1 (MetaCons "BytesLiteral" PrefixI True) ((S1 (MetaSel (Just "_stringLiteralAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: (S1 (MetaSel (Just "_unsafeBytesLiteralPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BytesPrefix) :*: S1 (MetaSel (Just "_stringLiteralStringType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 StringType))) :*: (S1 (MetaSel (Just "_stringLiteralQuoteType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QuoteType) :*: (S1 (MetaSel (Just "_stringLiteralValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PyChar]) :*: S1 (MetaSel (Just "_stringLiteralWhitespace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Whitespace]))))))

Lenses

Rendering

Extra functions

isEscape :: PyChar -> Bool Source #

Determine whether a PyChar is an escape character or not.