hpython-0.1: Syntax tree and DSL for Python

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

Language.Python.Syntax.CommaSep

Description

 
Synopsis

Documentation

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 #

HasTrailingWhitespace Comma Source # 
Instance details

Defined in Language.Python.Syntax.Punctuation

HasNewlines Comma Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' Comma Newline Source #

data CommaSep a Source #

Items separated by commas, with optional whitespace following each comma

Instances
Functor CommaSep Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

Foldable CommaSep Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

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

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

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

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

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

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

toList :: CommaSep a -> [a] #

null :: CommaSep a -> Bool #

length :: CommaSep a -> Int #

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

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

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

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

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

Traversable CommaSep Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

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

Defined in Language.Python.Syntax.CommaSep

Methods

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

show :: CommaSep a -> String #

showList :: [CommaSep a] -> ShowS #

Semigroup (CommaSep a) Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

(<>) :: CommaSep a -> CommaSep a -> CommaSep a #

sconcat :: NonEmpty (CommaSep a) -> CommaSep a #

stimes :: Integral b => b -> CommaSep a -> CommaSep a #

Monoid (CommaSep a) Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

mempty :: CommaSep a #

mappend :: CommaSep a -> CommaSep a -> CommaSep a #

mconcat :: [CommaSep a] -> CommaSep a #

HasNewlines a => HasNewlines (CommaSep a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (CommaSep a) Newline Source #

_CommaSep :: Iso (Maybe (a, [(Comma, a)], Maybe Comma)) (Maybe (b, [(Comma, b)], Maybe Comma)) (CommaSep a) (CommaSep b) Source #

Iso to unpack a CommaSep

csTrailingWhitespace :: HasTrailingWhitespace a => Traversal' (CommaSep a) [Whitespace] Source #

Traversal targeting the trailing whitespace in a comma separated list.

This can't be an instance of HasTrailingWhitespace because CommaSepNone never has trailing whitespace.

appendCommaSep :: [Whitespace] -> CommaSep a -> CommaSep a -> CommaSep a Source #

Appends two comma separated values together.

The provided whitespace is to follow the joining comma which is added

maybeToCommaSep :: Maybe a -> CommaSep a Source #

Convert a maybe to a singleton or nullary CommaSep

listToCommaSep :: [a] -> CommaSep a Source #

Convert a list to a CommaSep

Anywhere where whitespace is ambiguous, this function puts a single space

data CommaSep1 a Source #

Non-empty CommaSep

Constructors

CommaSepOne1 a 
CommaSepMany1 a Comma (CommaSep1 a) 
Instances
Functor CommaSep1 Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

Foldable CommaSep1 Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

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

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

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

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

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

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

toList :: CommaSep1 a -> [a] #

null :: CommaSep1 a -> Bool #

length :: CommaSep1 a -> Int #

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

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

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

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

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

Traversable CommaSep1 Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

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

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

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

Defined in Language.Python.Syntax.CommaSep

Methods

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

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

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

Defined in Language.Python.Syntax.CommaSep

Semigroup (CommaSep1 a) Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

(<>) :: CommaSep1 a -> CommaSep1 a -> CommaSep1 a #

sconcat :: NonEmpty (CommaSep1 a) -> CommaSep1 a #

stimes :: Integral b => b -> CommaSep1 a -> CommaSep1 a #

HasTrailingWhitespace s => HasTrailingWhitespace (CommaSep1 s) Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

HasNewlines a => HasNewlines (CommaSep1 a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (CommaSep1 a) Newline Source #

commaSep1Head :: CommaSep1 a -> a Source #

Get the first element of a CommaSep1

appendCommaSep1 :: [Whitespace] -> CommaSep1 a -> CommaSep1 a -> CommaSep1 a Source #

Appends two non-empty comma separated values together.

The provided whitespace is to follow the joining comma which is added

listToCommaSep1 :: NonEmpty a -> CommaSep1 a Source #

Convert a NonEmpty to a CommaSep1

Anywhere where whitespace is ambiguous, this function puts a single space

listToCommaSep1' :: [a] -> Maybe (CommaSep1' a) Source #

Attempt to insert comma separators into a list, which will not be terminated by a comma.

If the list is empty, Nothing is returned.

data CommaSep1' a Source #

Non-empty CommaSep, optionally terminated by a comma

Assumes that the contents consumes trailing whitespace

Instances
Functor CommaSep1' Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

fmap :: (a -> b) -> CommaSep1' a -> CommaSep1' b #

(<$) :: a -> CommaSep1' b -> CommaSep1' a #

Foldable CommaSep1' Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

fold :: Monoid m => CommaSep1' m -> m #

foldMap :: Monoid m => (a -> m) -> CommaSep1' a -> m #

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

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

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

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

foldr1 :: (a -> a -> a) -> CommaSep1' a -> a #

foldl1 :: (a -> a -> a) -> CommaSep1' a -> a #

toList :: CommaSep1' a -> [a] #

null :: CommaSep1' a -> Bool #

length :: CommaSep1' a -> Int #

elem :: Eq a => a -> CommaSep1' a -> Bool #

maximum :: Ord a => CommaSep1' a -> a #

minimum :: Ord a => CommaSep1' a -> a #

sum :: Num a => CommaSep1' a -> a #

product :: Num a => CommaSep1' a -> a #

Traversable CommaSep1' Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

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

sequenceA :: Applicative f => CommaSep1' (f a) -> f (CommaSep1' a) #

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

sequence :: Monad m => CommaSep1' (m a) -> m (CommaSep1' a) #

Eq a => Eq (CommaSep1' a) Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

Methods

(==) :: CommaSep1' a -> CommaSep1' a -> Bool #

(/=) :: CommaSep1' a -> CommaSep1' a -> Bool #

Show a => Show (CommaSep1' a) Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

HasTrailingWhitespace s => HasTrailingWhitespace (CommaSep1' s) Source # 
Instance details

Defined in Language.Python.Syntax.CommaSep

HasNewlines a => HasNewlines (CommaSep1' a) Source # 
Instance details

Defined in Language.Python.Optics.Newlines

Methods

_Newlines :: Traversal' (CommaSep1' a) Newline Source #

_CommaSep1' :: Iso (a, [(Comma, a)], Maybe Comma) (b, [(Comma, b)], Maybe Comma) (CommaSep1' a) (CommaSep1' b) Source #

Iso to unpack a CommaSep1'