Copyright | (C) CSIRO 2017-2019 |
---|---|
License | BSD3 |
Maintainer | Isaac Elliott <isaace71295@gmail.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Python string literals.
See https://docs.python.org/3.5/reference/lexical_analysis.html#string-and-bytes-literals
Synopsis
- data PyChar
- = Char_newline
- | Char_octal1 OctDigit
- | Char_octal2 OctDigit OctDigit
- | Char_octal3 OctDigit OctDigit OctDigit
- | Char_hex HeXDigit HeXDigit
- | Char_uni16 HeXDigit HeXDigit HeXDigit HeXDigit
- | Char_uni32 HeXDigit HeXDigit HeXDigit HeXDigit HeXDigit HeXDigit HeXDigit HeXDigit
- | Char_esc_bslash
- | Char_esc_singlequote
- | Char_esc_doublequote
- | Char_esc_a
- | Char_esc_b
- | Char_esc_f
- | Char_esc_n
- | Char_esc_r
- | Char_esc_t
- | Char_esc_v
- | Char_lit Char
- fromHaskellString :: String -> [PyChar]
- data QuoteType
- data StringType
- data StringPrefix
- data RawStringPrefix
- data BytesPrefix
- data RawBytesPrefix
- hasPrefix :: StringLiteral a -> Bool
- data StringLiteral a
- = RawStringLiteral { }
- | StringLiteral { }
- | RawBytesLiteral { }
- | BytesLiteral { }
- stringLiteralStringType :: forall a. Lens' (StringLiteral a) StringType
- stringLiteralQuoteType :: forall a. Lens' (StringLiteral a) QuoteType
- stringLiteralValue :: forall a. Lens' (StringLiteral a) [PyChar]
- stringLiteralWhitespace :: forall a. Lens' (StringLiteral a) [Whitespace]
- showQuoteType :: QuoteType -> Char
- showStringPrefix :: StringPrefix -> Text
- showRawStringPrefix :: RawStringPrefix -> Text
- showBytesPrefix :: BytesPrefix -> Text
- showRawBytesPrefix :: RawBytesPrefix -> Text
- isEscape :: PyChar -> Bool
Datatypes
Characters
A character in a string literal. This is a large sum type, with a
catch-all of a Haskell Char
.
Instances
fromHaskellString :: String -> [PyChar] Source #
Convert a Haskell string to a list of PyChar
. This is useful when
writing Python in Haskell.
String information
Double or single quotation marks?
"Double quotes" """Double quotes""" 'Single quotes' '''Single quotes'''
data StringType Source #
Three pairs of quotations or one?
"""Long string""" '''Also long string''' "Short string" 'Also short string'
Instances
Eq StringType Source # | |
Defined in Language.Python.Syntax.Strings (==) :: StringType -> StringType -> Bool # (/=) :: StringType -> StringType -> Bool # | |
Ord StringType Source # | |
Defined in Language.Python.Syntax.Strings compare :: StringType -> StringType -> Ordering # (<) :: StringType -> StringType -> Bool # (<=) :: StringType -> StringType -> Bool # (>) :: StringType -> StringType -> Bool # (>=) :: StringType -> StringType -> Bool # max :: StringType -> StringType -> StringType # min :: StringType -> StringType -> StringType # | |
Show StringType Source # | |
Defined in Language.Python.Syntax.Strings showsPrec :: Int -> StringType -> ShowS # show :: StringType -> String # showList :: [StringType] -> ShowS # | |
Generic StringType Source # | |
Defined in Language.Python.Syntax.Strings type Rep StringType :: Type -> Type # from :: StringType -> Rep StringType x # to :: Rep StringType x -> StringType # | |
type Rep StringType Source # | |
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.
Instances
Eq StringPrefix Source # | |
Defined in Language.Python.Syntax.Strings (==) :: StringPrefix -> StringPrefix -> Bool # (/=) :: StringPrefix -> StringPrefix -> Bool # | |
Ord StringPrefix Source # | |
Defined in Language.Python.Syntax.Strings compare :: StringPrefix -> StringPrefix -> Ordering # (<) :: StringPrefix -> StringPrefix -> Bool # (<=) :: StringPrefix -> StringPrefix -> Bool # (>) :: StringPrefix -> StringPrefix -> Bool # (>=) :: StringPrefix -> StringPrefix -> Bool # max :: StringPrefix -> StringPrefix -> StringPrefix # min :: StringPrefix -> StringPrefix -> StringPrefix # | |
Show StringPrefix Source # | |
Defined in Language.Python.Syntax.Strings showsPrec :: Int -> StringPrefix -> ShowS # show :: StringPrefix -> String # showList :: [StringPrefix] -> ShowS # | |
Generic StringPrefix Source # | |
Defined in Language.Python.Syntax.Strings type Rep StringPrefix :: Type -> Type # from :: StringPrefix -> Rep StringPrefix x # to :: Rep StringPrefix x -> StringPrefix # | |
type Rep StringPrefix Source # | |
data RawStringPrefix Source #
Raw strings are prefixed with either r
or R
.
Instances
data BytesPrefix Source #
This prefix indicates it's a bytes literal rather than a string literal.
Instances
Eq BytesPrefix Source # | |
Defined in Language.Python.Syntax.Strings (==) :: BytesPrefix -> BytesPrefix -> Bool # (/=) :: BytesPrefix -> BytesPrefix -> Bool # | |
Ord BytesPrefix Source # | |
Defined in Language.Python.Syntax.Strings compare :: BytesPrefix -> BytesPrefix -> Ordering # (<) :: BytesPrefix -> BytesPrefix -> Bool # (<=) :: BytesPrefix -> BytesPrefix -> Bool # (>) :: BytesPrefix -> BytesPrefix -> Bool # (>=) :: BytesPrefix -> BytesPrefix -> Bool # max :: BytesPrefix -> BytesPrefix -> BytesPrefix # min :: BytesPrefix -> BytesPrefix -> BytesPrefix # | |
Show BytesPrefix Source # | |
Defined in Language.Python.Syntax.Strings showsPrec :: Int -> BytesPrefix -> ShowS # show :: BytesPrefix -> String # showList :: [BytesPrefix] -> ShowS # | |
Generic BytesPrefix Source # | |
Defined in Language.Python.Syntax.Strings type Rep BytesPrefix :: Type -> Type # from :: BytesPrefix -> Rep BytesPrefix x # to :: Rep BytesPrefix x -> BytesPrefix # | |
type Rep BytesPrefix Source # | |
data RawBytesPrefix Source #
A string of raw bytes can be indicated by a number of prefixes
Instances
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 PyChar
s.
Like many other data types in hpython, it has an annotation and trailing whitespace.
Instances
Lenses
stringLiteralStringType :: forall a. Lens' (StringLiteral a) StringType Source #
stringLiteralQuoteType :: forall a. Lens' (StringLiteral a) QuoteType Source #
stringLiteralValue :: forall a. Lens' (StringLiteral a) [PyChar] Source #
stringLiteralWhitespace :: forall a. Lens' (StringLiteral a) [Whitespace] Source #
Rendering
showQuoteType :: QuoteType -> Char Source #
showStringPrefix :: StringPrefix -> Text Source #
showBytesPrefix :: BytesPrefix -> Text Source #