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

Description

 
Synopsis

Documentation

data Comment a Source #

A Python single-line comment, such as on the following line:

y = x + 4 # add four to the value of x

In this case, the structure parsed would be

MkComment () " add four to the value of x"

with the hash being inferred, and the space after the hash being preserved.

Python does not have multi-line comments. There is a common convention of using a multi-line string expression as a multi-line comment, since a string expression is a no-op statement. Such multi-line comments are NOT represented with this data type, but rather as normal string expressions (since that's what they are).

Constructors

MkComment 
Instances
Functor Comment Source # 
Instance details

Defined in Language.Python.Syntax.Comment

Methods

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

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

Foldable Comment Source # 
Instance details

Defined in Language.Python.Syntax.Comment

Methods

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

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

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

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

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

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

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

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

toList :: Comment a -> [a] #

null :: Comment a -> Bool #

length :: Comment a -> Int #

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

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

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

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

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

Traversable Comment Source # 
Instance details

Defined in Language.Python.Syntax.Comment

Methods

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

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

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

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

Eq1 Comment Source # 
Instance details

Defined in Language.Python.Syntax.Comment

Methods

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

Ord1 Comment Source # 
Instance details

Defined in Language.Python.Syntax.Comment

Methods

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

HasAnn Comment Source # 
Instance details

Defined in Language.Python.Syntax.Comment

Methods

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

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

Defined in Language.Python.Syntax.Comment

Methods

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

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

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

Defined in Language.Python.Syntax.Comment

Methods

compare :: Comment a -> Comment a -> Ordering #

(<) :: Comment a -> Comment a -> Bool #

(<=) :: Comment a -> Comment a -> Bool #

(>) :: Comment a -> Comment a -> Bool #

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

max :: Comment a -> Comment a -> Comment a #

min :: Comment a -> Comment a -> Comment a #

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

Defined in Language.Python.Syntax.Comment

Methods

showsPrec :: Int -> Comment a -> ShowS #

show :: Comment a -> String #

showList :: [Comment a] -> ShowS #

Generic (Comment a) Source # 
Instance details

Defined in Language.Python.Syntax.Comment

Associated Types

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

Methods

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

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

type Rep (Comment a) Source # 
Instance details

Defined in Language.Python.Syntax.Comment

type Rep (Comment a) = D1 (MetaData "Comment" "Language.Python.Syntax.Comment" "hpython-0.2-7fNN6PEHntyHCqZaN2NGK0" False) (C1 (MetaCons "MkComment" PrefixI True) (S1 (MetaSel (Just "_commentAnn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann a)) :*: S1 (MetaSel (Just "_commentValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))