1
1
mirror of https://github.com/google/ormolu.git synced 2024-11-23 22:27:16 +03:00

Various minor corrections to the docs and code

This commit is contained in:
mrkkrp 2019-05-08 23:03:20 +02:00 committed by Mark Karpov
parent b9c8b64947
commit 0d558f1cb6
8 changed files with 59 additions and 44 deletions

View File

@ -21,13 +21,14 @@ import qualified Data.List.NonEmpty as NE
import qualified GHC
import qualified Lexer as GHC
-- | A stream of 'RealLocated' comment strings in ascending order with
-- respect to beginning of corresponding spans.
-- | A stream of 'RealLocated' 'Comment's in ascending order with respect to
-- beginning of corresponding spans.
newtype CommentStream = CommentStream [RealLocated Comment]
deriving (Eq, Data, Semigroup, Monoid)
-- | A wrapper for a single comment.
-- | A wrapper for a single comment. The 'NonEmpty' list inside contains
-- lines of multiline comment @{- … -}@ or just single item\/line otherwise.
newtype Comment = Comment (NonEmpty String)
deriving (Eq, Show, Data)
@ -48,13 +49,15 @@ mkCommentStream extraComments pstate
. mapMaybe toRealSpan $
extraComments ++
(fmap unAnnotationComment <$> GHC.comment_q pstate) ++
concatMap (fmap (fmap unAnnotationComment) . snd) (GHC.annotations_comments pstate)
concatMap (fmap (fmap unAnnotationComment) . snd)
(GHC.annotations_comments pstate)
where
startOfSpan (L l _) = realSrcSpanStart l
toRealSpan (L (RealSrcSpan l) a) = Just (L l a)
toRealSpan _ = Nothing
-- | Test whether a 'Comment' looks like a Haddock following a definition.
-- | Test whether a 'Comment' looks like a Haddock following a definition,
-- i.e. something starting with @-- ^@.
isPrevHaddock :: Comment -> Bool
isPrevHaddock (Comment (x :| _)) = "-- ^" `isPrefixOf` x

View File

@ -18,8 +18,8 @@ import Ormolu.Imports (sortImports)
-- positions.
diff
:: (CommentStream, ParsedSource) -- ^ First annotated AST
-> (CommentStream, ParsedSource) -- ^ Second annotated AST
:: (CommentStream, ParsedSource) -- ^ First comment stream and AST
-> (CommentStream, ParsedSource) -- ^ Second comment stream and AST
-> Bool
diff (cstream0, ps0) (cstream1, ps1) =
not (matchIgnoringSrcSpans cstream0 cstream1)

View File

@ -15,7 +15,7 @@ import System.IO
import qualified GHC
import qualified Outputable as GHC
-- | Ormolu exception representing all cases when 'ormoluFile' can fail.
-- | Ormolu exception representing all cases when Ormolu can fail.
data OrmoluException
= OrmoluCppEnabled

View File

@ -15,15 +15,15 @@ module Ormolu.Printer.Combinators
, newline
, inci
, relaxComments
, hasMoreComments
, located
, locatedVia
, located'
, switchLayout
, velt
, velt'
, vlayout
, breakpoint
-- ** Formatting lists
, velt
, velt'
, withSep
, spaceSep
, newlineSep
@ -66,7 +66,7 @@ txt t = ensureIndent >> spit t
atom :: Outputable a => a -> R ()
atom = txt . T.pack . showSDocUnsafe . ppr
-- | Enter a 'Located' entity. This primitive handles outputting comments
-- | Enter a 'Located' entity. This combinator handles outputting comments
-- that may be associated with the primitive and sets corresponding layout
-- for the inner computation.
@ -77,7 +77,7 @@ located
-> R ()
located loc@(L l _) = locatedVia (Just l) loc
-- | A special version of 'located' that allows to control layout using
-- | A special version of 'located' that allows to control layout using an
-- externally provided span. 'Nothing' means that layout won't be changed.
locatedVia
@ -129,6 +129,15 @@ switchLayout spn = enterLayout
then SingleLine
else MultiLine)
-- | Insert a space if enclosing layout is single-line, or newline if it's
-- multiline.
breakpoint :: R ()
breakpoint = vlayout space newline
----------------------------------------------------------------------------
-- Formatting lists
-- | Element of variable layout. This means that the sub-components may be
-- rendered either on single line or each on its own line depending on
-- current layout.
@ -151,12 +160,6 @@ velt' xs = sitcc $ sequence_ (intersperse sep (sitcc <$> xs))
where
sep = vlayout (spit " ") newline
-- | Insert a space if enclosing layout is single-line, or newline if it's
-- multiline.
breakpoint :: R ()
breakpoint = vlayout space newline
-- | Put separator between renderings of items of a list.
withSep
@ -199,9 +202,12 @@ line m = do
-- | Surround given entity by backticks.
backticks :: R () -> R ()
backticks m = txt "`" >> m >> txt "`"
backticks m = do
txt "`"
m
txt "`"
-- | Surround given entity by curly braces.
-- | Surround given entity by curly braces @{@ and @}@.
braces :: R () -> R ()
braces m = sitcc $ do
@ -209,7 +215,7 @@ braces m = sitcc $ do
ospaces m
txt "}"
-- | Surround given entity by square brackets.
-- | Surround given entity by square brackets @[@ and @]@.
brackets :: R () -> R ()
brackets m = sitcc $ do
@ -217,7 +223,7 @@ brackets m = sitcc $ do
ospaces m
txt "]"
-- | Surround given entity by parallel array brackets @[:@ ond @:]@.
-- | Surround given entity by parallel array brackets @[:@ and @:]@.
bracketsPar :: R () -> R ()
bracketsPar m = sitcc $ do
@ -225,7 +231,7 @@ bracketsPar m = sitcc $ do
m
txt ":]"
-- | Surround given entity by parentheses.
-- | Surround given entity by parentheses @(@ and @)@.
parens :: R () -> R ()
parens m = sitcc $ do

View File

@ -1,12 +1,14 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Helpers for formatting of comments.
-- | Helpers for formatting of comments. This is low-level code, use
-- "Ormolu.Printer.Combinators" unless you know what you are doing.
module Ormolu.Printer.Comments
( spitPrecedingComments
, spitFollowingComments
, spitRemainingComments
, hasMoreComments
)
where
@ -80,11 +82,11 @@ spitFollowingComment (L ref a) mlastSpn = do
i <- getIndent
withPoppedComment (commentFollowsElt ref mnSpn meSpn mlastSpn) $ \l comment ->
if theSameLine l ref && not (isModule a)
then modNextline $ \m -> setIndent i $ do
then modNewline $ \m -> setIndent i $ do
spit " "
spitComment comment
m
else modNextline $ \m -> setIndent i $ do
else modNewline $ \m -> setIndent i $ do
m
when (needsNewlineBefore l mlastSpn) newline
spitComment comment

View File

@ -14,7 +14,7 @@ module Ormolu.Printer.Internal
-- * Internal functions
, spit
, newline
, modNextline
, modNewline
, ensureIndent
, inci
, sitcc
@ -137,13 +137,7 @@ spit x = do
}
traceR "spit_after" Nothing
-- | Output a newline. The 'modNewline' function can be used to alter what
-- will be inserted. This is used to output comments following an element of
-- AST because we cannot output comments immediately, e.g. because we need
-- to close parentheses first, etc.
--
-- 'newline' auto-resets its modifications so the changes introduced with
-- 'modNewline' only have effect once.
-- | Output a newline.
newline :: R ()
newline = do
@ -165,11 +159,18 @@ newlineRaw = do
}
traceR "newline_after" Nothing
-- | Modify how next newline will be output. The argument of call-back is
-- the version of 'newline' built so far.
-- | The 'modNewline' function can be used to alter what will be inserted as
-- a newline. This is used to output comments following an element of AST
-- because we cannot output comments immediately, e.g. because we need to
-- close parentheses first, etc.
--
-- 'newline' auto-resets its modifications so the changes introduced with
-- 'modNewline' only have effect once.
--
-- The argument of the call-back is the version of 'newline' built so far.
modNextline :: (R () -> R ()) -> R ()
modNextline f = R $ do
modNewline :: (R () -> R ()) -> R ()
modNewline f = R $ do
old <- gets scNewline
modify $ \sc -> sc
{ scNewline = f old
@ -311,7 +312,7 @@ hasMoreComments = R $ do
getIndent :: R Int
getIndent = R (asks rcIndent)
-- | Set indentation level.
-- | Set indentation level for the given computation.
setIndent :: Int -> R () -> R ()
setIndent i m' = do

View File

@ -1,7 +1,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-- | Build span stream of AST elements.
-- | Build span stream from AST.
module Ormolu.SpanStream
( SpanStream (..)
@ -24,7 +24,8 @@ import qualified Data.DList as D
newtype SpanStream = SpanStream [RealSrcSpan]
deriving (Eq, Show, Data, Semigroup, Monoid)
-- | Create 'SpanStream' from a data structure containing 'RealSrcSpan's.
-- | Create 'SpanStream' from a data structure containing \"located\"
-- elements.
mkSpanStream
:: Data a

View File

@ -1,3 +1,5 @@
-- | Random utilities used by the code.
module Ormolu.Utils
( combineSrcSpans'
, isModule
@ -20,9 +22,9 @@ combineSrcSpans' (x:|xs) = foldr combineSrcSpans x xs
isModule :: Data a => a -> Bool
isModule x = showConstr (toConstr x) == "HsModule"
-- | Exact inner value from 'Located'.
-- | Exact inner value from a 'Located' thing.
unL :: Located e -> e
unL :: GenLocated l e -> e
unL (L _ e) = e
-- | Get source span from a 'Located' thing.