License | BSD-3-Clause |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
Swarm.Language.Syntax.Comments
Description
Types for working with comments in Swarm programming language.
Synopsis
- data CommentType
- data CommentSituation
- isStandalone :: Comment -> Bool
- data Comment = Comment {}
- data Comments = Comments {}
- beforeComments :: Lens' Comments (Seq Comment)
- afterComments :: Lens' Comments (Seq Comment)
Documentation
data CommentType Source #
Line vs block comments.
Constructors
LineComment | |
BlockComment |
Instances
data CommentSituation Source #
Was a comment all by itself on a line, or did it occur after some other tokens on a line?
Constructors
StandaloneComment | |
SuffixComment |
Instances
FromJSON CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods parseJSON :: Value -> Parser CommentSituation # parseJSONList :: Value -> Parser [CommentSituation] # | |||||
ToJSON CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods toJSON :: CommentSituation -> Value # toEncoding :: CommentSituation -> Encoding # toJSONList :: [CommentSituation] -> Value # toEncodingList :: [CommentSituation] -> Encoding # omitField :: CommentSituation -> Bool # | |||||
Data CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CommentSituation -> c CommentSituation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CommentSituation # toConstr :: CommentSituation -> Constr # dataTypeOf :: CommentSituation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CommentSituation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CommentSituation) # gmapT :: (forall b. Data b => b -> b) -> CommentSituation -> CommentSituation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CommentSituation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CommentSituation -> r # gmapQ :: (forall d. Data d => d -> u) -> CommentSituation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CommentSituation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CommentSituation -> m CommentSituation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CommentSituation -> m CommentSituation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CommentSituation -> m CommentSituation # | |||||
Bounded CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments | |||||
Enum CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods succ :: CommentSituation -> CommentSituation # pred :: CommentSituation -> CommentSituation # toEnum :: Int -> CommentSituation # fromEnum :: CommentSituation -> Int # enumFrom :: CommentSituation -> [CommentSituation] # enumFromThen :: CommentSituation -> CommentSituation -> [CommentSituation] # enumFromTo :: CommentSituation -> CommentSituation -> [CommentSituation] # enumFromThenTo :: CommentSituation -> CommentSituation -> CommentSituation -> [CommentSituation] # | |||||
Generic CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Associated Types
Methods from :: CommentSituation -> Rep CommentSituation x # to :: Rep CommentSituation x -> CommentSituation # | |||||
Read CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods readsPrec :: Int -> ReadS CommentSituation # readList :: ReadS [CommentSituation] # | |||||
Show CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods showsPrec :: Int -> CommentSituation -> ShowS # show :: CommentSituation -> String # showList :: [CommentSituation] -> ShowS # | |||||
Eq CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods (==) :: CommentSituation -> CommentSituation -> Bool # (/=) :: CommentSituation -> CommentSituation -> Bool # | |||||
Ord CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods compare :: CommentSituation -> CommentSituation -> Ordering # (<) :: CommentSituation -> CommentSituation -> Bool # (<=) :: CommentSituation -> CommentSituation -> Bool # (>) :: CommentSituation -> CommentSituation -> Bool # (>=) :: CommentSituation -> CommentSituation -> Bool # max :: CommentSituation -> CommentSituation -> CommentSituation # min :: CommentSituation -> CommentSituation -> CommentSituation # | |||||
Hashable CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments | |||||
type Rep CommentSituation Source # | |||||
Defined in Swarm.Language.Syntax.Comments |
isStandalone :: Comment -> Bool Source #
Test whether a comment is a standalone comment or not.
A comment is retained as some text plus metadata (source location, comment type, + comment situation). While parsing we record all comments out-of-band, for later re-insertion into the AST.
Constructors
Comment | |
Fields |
Instances
FromJSON Comment Source # | |||||
Defined in Swarm.Language.Syntax.Comments | |||||
ToJSON Comment Source # | |||||
Data Comment Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Comment -> c Comment # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Comment # toConstr :: Comment -> Constr # dataTypeOf :: Comment -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Comment) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment) # gmapT :: (forall b. Data b => b -> b) -> Comment -> Comment # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQ :: (forall d. Data d => d -> u) -> Comment -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Comment -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # | |||||
Generic Comment Source # | |||||
Defined in Swarm.Language.Syntax.Comments Associated Types
| |||||
Show Comment Source # | |||||
Eq Comment Source # | |||||
Hashable Comment Source # | |||||
Defined in Swarm.Language.Syntax.Comments | |||||
PrettyPrec Comment Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods prettyPrec :: Int -> Comment -> Doc ann | |||||
type Rep Comment Source # | |||||
Defined in Swarm.Language.Syntax.Comments type Rep Comment = D1 ('MetaData "Comment" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Comment" 'PrefixI 'True) ((S1 ('MetaSel ('Just "commentSrcLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SrcLoc) :*: S1 ('MetaSel ('Just "commentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentType)) :*: (S1 ('MetaSel ('Just "commentSituation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommentSituation) :*: S1 ('MetaSel ('Just "commentText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))) |
Comments which can be attached to a particular AST node. Some comments come textually before the node and some come after.
Constructors
Comments | |
Fields |
Instances
FromJSON Comments Source # | |||||
Defined in Swarm.Language.Syntax.Comments | |||||
ToJSON Comments Source # | |||||
Data Comments Source # | |||||
Defined in Swarm.Language.Syntax.Comments Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Comments -> c Comments # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Comments # toConstr :: Comments -> Constr # dataTypeOf :: Comments -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Comments) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comments) # gmapT :: (forall b. Data b => b -> b) -> Comments -> Comments # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Comments -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comments -> r # gmapQ :: (forall d. Data d => d -> u) -> Comments -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Comments -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comments -> m Comments # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comments -> m Comments # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comments -> m Comments # | |||||
Monoid Comments Source # | |||||
Semigroup Comments Source # | |||||
Generic Comments Source # | |||||
Defined in Swarm.Language.Syntax.Comments Associated Types
| |||||
Show Comments Source # | |||||
Eq Comments Source # | |||||
Hashable Comments Source # | |||||
Defined in Swarm.Language.Syntax.Comments | |||||
AsEmpty Comments Source # | |||||
Defined in Swarm.Language.Syntax.Comments | |||||
type Rep Comments Source # | |||||
Defined in Swarm.Language.Syntax.Comments type Rep Comments = D1 ('MetaData "Comments" "Swarm.Language.Syntax.Comments" "swarm-0.7.0.0-IuFfgHrMoE7JrptOBRVOwx-swarm-lang" 'False) (C1 ('MetaCons "Comments" 'PrefixI 'True) (S1 ('MetaSel ('Just "_beforeComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Comment)) :*: S1 ('MetaSel ('Just "_afterComments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq Comment)))) |