Skip to content

Commit

Permalink
Improved formatting. Switch to prettyprinter library. Tracing.
Browse files Browse the repository at this point in the history
  • Loading branch information
newhoggy committed Jul 21, 2021
1 parent 29898f1 commit ca02c8e
Show file tree
Hide file tree
Showing 12 changed files with 333 additions and 98 deletions.
3 changes: 2 additions & 1 deletion optparse-applicative.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ library
, Options.Applicative.Common
, Options.Applicative.Extra
, Options.Applicative.Help
, Options.Applicative.Help.Ann
, Options.Applicative.Help.Chunk
, Options.Applicative.Help.Core
, Options.Applicative.Help.Levenshtein
Expand All @@ -99,7 +100,7 @@ library
build-depends: base == 4.*
, transformers >= 0.2 && < 0.6
, transformers-compat >= 0.3 && < 0.7
, ansi-wl-pprint >= 0.6.8 && < 0.7
, prettyprinter >= 1.7.0 && < 1.8

if flag(process)
build-depends: process >= 1.0 && < 1.7
Expand Down
3 changes: 3 additions & 0 deletions src/Options/Applicative.hs
Original file line number Diff line number Diff line change
Expand Up @@ -94,6 +94,9 @@ module Options.Applicative (
showDefault,
metavar,
noArgError,
helpAlignUsageOverflow,
helpHangUsageOverflow,
helpRenderHelp,
hidden,
internal,
style,
Expand Down
2 changes: 1 addition & 1 deletion src/Options/Applicative/BashCompletion.hs
Original file line number Diff line number Diff line change
Expand Up @@ -142,7 +142,7 @@ bashCompletionQuery pinfo pprefs richness ws i _ = case runCompletion compl ppre
-- If there was a line break, it would come across as a different completion
-- possibility.
render_line :: Int -> Doc -> String
render_line len doc = case lines (displayS (renderPretty 1 len doc) "") of
render_line len doc = case lines (renderShowS (layoutPretty (LayoutOptions (AvailablePerLine len 1.0)) doc) "") of
[] -> ""
[x] -> x
x : _ -> x ++ "..."
Expand Down
23 changes: 21 additions & 2 deletions src/Options/Applicative/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,10 @@ module Options.Applicative.Builder (
columns,
helpLongEquals,
helpShowGlobals,
helpAlignUsageOverflow,
helpHangUsageOverflow,
helpIndent,
helpRenderHelp,
prefs,
defaultPrefs,

Expand Down Expand Up @@ -116,8 +119,9 @@ import Options.Applicative.Builder.Completer
import Options.Applicative.Builder.Internal
import Options.Applicative.Common
import Options.Applicative.Types
import Options.Applicative.Help.Pretty
import Options.Applicative.Help.Chunk
import Options.Applicative.Help.Pretty
import Options.Applicative.Help.Types (renderHelp)

-- Readers --

Expand Down Expand Up @@ -521,6 +525,18 @@ helpLongEquals = PrefsMod $ \p -> p { prefHelpLongEquals = True }
helpShowGlobals :: PrefsMod
helpShowGlobals = PrefsMod $ \p -> p { prefHelpShowGlobal = True }

-- | Align usage overflow to the right
helpAlignUsageOverflow :: PrefsMod
helpAlignUsageOverflow = PrefsMod $ \p -> p { prefUsageOverflow = UsageOverflowAlign }

-- | Hang usage overflow to the specified indent
helpHangUsageOverflow :: Int -> PrefsMod
helpHangUsageOverflow indentation = PrefsMod $ \p -> p { prefUsageOverflow = UsageOverflowHang indentation }

-- | Custom render function
helpRenderHelp :: (Int -> ParserHelp -> String) -> PrefsMod
helpRenderHelp f = PrefsMod $ \p -> p { prefRenderHelp = f }

-- | Set fill width in help text presentation.
helpIndent :: Int -> PrefsMod
helpIndent w = PrefsMod $ \p -> p { prefTabulateFill = w }
Expand All @@ -540,7 +556,10 @@ prefs m = applyPrefsMod m base
, prefColumns = 80
, prefHelpLongEquals = False
, prefHelpShowGlobal = False
, prefTabulateFill = 24 }
, prefUsageOverflow = UsageOverflowAlign
, prefTabulateFill = 24
, prefRenderHelp = renderHelp
}

-- Convenience shortcuts

Expand Down
21 changes: 14 additions & 7 deletions src/Options/Applicative/Extra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ module Options.Applicative.Extra (
handleParseResult,
parserFailure,
renderFailure,
renderFailure',
ParserFailure(..),
overFailure,
ParserResult(..),
Expand Down Expand Up @@ -104,19 +105,22 @@ execParser = customExecParser defaultPrefs
customExecParser :: ParserPrefs -> ParserInfo a -> IO a
customExecParser pprefs pinfo
= execParserPure pprefs pinfo <$> getArgs
>>= handleParseResult
>>= handleParseResult' pprefs

-- | Handle `ParserResult`.
handleParseResult :: ParserResult a -> IO a
handleParseResult (Success a) = return a
handleParseResult (Failure failure) = do
handleParseResult = handleParseResult' defaultPrefs

handleParseResult' :: ParserPrefs -> ParserResult a -> IO a
handleParseResult' _ (Success a) = return a
handleParseResult' pprefs (Failure failure) = do
progn <- getProgName
let (msg, exit) = renderFailure failure progn
let (msg, exit) = renderFailure' pprefs failure progn
case exit of
ExitSuccess -> putStrLn msg
_ -> hPutStrLn stderr msg
exitWith exit
handleParseResult (CompletionInvoked compl) = do
handleParseResult' _ (CompletionInvoked compl) = do
progn <- getProgName
msg <- execCompletion compl progn
putStr msg
Expand Down Expand Up @@ -328,6 +332,9 @@ parserFailure pprefs pinfo msg ctx0 = ParserFailure $ \progn ->
_ -> prefShowHelpOnError pprefs

renderFailure :: ParserFailure ParserHelp -> String -> (String, ExitCode)
renderFailure failure progn =
renderFailure = renderFailure' defaultPrefs

renderFailure' :: ParserPrefs -> ParserFailure ParserHelp -> String -> (String, ExitCode)
renderFailure' pprefs failure progn =
let (h, exit, cols) = execFailure failure progn
in (renderHelp cols h, exit)
in (prefRenderHelp pprefs cols h, exit)
22 changes: 22 additions & 0 deletions src/Options/Applicative/Help/Ann.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
{-# LANGUAGE FlexibleInstances #-}

module Options.Applicative.Help.Ann (
Ann(..),
CanAnnotate(..)
) where

import Prettyprinter (Doc, annotate)

data Ann = AnnTrace Int String
deriving (Eq, Show)

class CanAnnotate a where
-- | Annotate trace a value
annTrace
:: Int -- ^ Trace level
-> String -- ^ Trace message
-> a -- ^ Value to be traced
-> a -- ^ The traced value

instance CanAnnotate (Doc Ann) where
annTrace n = annotate . AnnTrace n
39 changes: 29 additions & 10 deletions src/Options/Applicative/Help/Chunk.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE FlexibleInstances #-}

module Options.Applicative.Help.Chunk
( Chunk(..)
, chunked
Expand All @@ -11,6 +13,8 @@ module Options.Applicative.Help.Chunk
, paragraph
, extractChunk
, tabulate
, chunkFlatAlt
, chunkIsEffectivelyEmpty
) where

import Control.Applicative
Expand All @@ -20,13 +24,17 @@ import Data.Maybe
import Data.Semigroup
import Prelude

import Options.Applicative.Help.Ann
import Options.Applicative.Help.Pretty

-- | The free monoid on a semigroup 'a'.
newtype Chunk a = Chunk
{ unChunk :: Maybe a }
deriving (Eq, Show)

instance CanAnnotate (Chunk Doc) where
annTrace n = fmap . annTrace n

instance Functor Chunk where
fmap f = Chunk . fmap f . unChunk

Expand Down Expand Up @@ -89,20 +97,20 @@ extractChunk = fromMaybe mempty . unChunk
-- Unlike '<+>' for 'Doc', this operation has a unit element, namely the empty
-- 'Chunk'.
(<<+>>) :: Chunk Doc -> Chunk Doc -> Chunk Doc
(<<+>>) = chunked (<+>)
(<<+>>) = fmap (annTrace 1 "(<<+>>)") . chunked (<+>)

-- | Concatenate two 'Chunk's with a softline in between. This is exactly like
-- '<<+>>', but uses a softline instead of a space.
(<</>>) :: Chunk Doc -> Chunk Doc -> Chunk Doc
(<</>>) = chunked (</>)
(<</>>) = fmap (annTrace 1 "(<</>>)") . chunked (</>)

-- | Concatenate 'Chunk's vertically.
vcatChunks :: [Chunk Doc] -> Chunk Doc
vcatChunks = foldr (chunked (.$.)) mempty
vcatChunks = fmap (annTrace 1 "vcatChunks") . foldr (chunked (.$.)) mempty

-- | Concatenate 'Chunk's vertically separated by empty lines.
vsepChunks :: [Chunk Doc] -> Chunk Doc
vsepChunks = foldr (chunked (\x y -> x .$. mempty .$. y)) mempty
vsepChunks = annTrace 1 "vsepChunks" . foldr (chunked (\x y -> x .$. mempty .$. y)) mempty

-- | Whether a 'Chunk' is empty. Note that something like 'pure mempty' is not
-- considered an empty chunk, even though the underlying 'Doc' is empty.
Expand All @@ -114,8 +122,8 @@ isEmpty = isNothing . unChunk
-- > isEmpty . stringChunk = null
-- > extractChunk . stringChunk = string
stringChunk :: String -> Chunk Doc
stringChunk "" = mempty
stringChunk s = pure (string s)
stringChunk "" = annTrace 0 "stringChunk" mempty
stringChunk s = annTrace 0 "stringChunk" $ pure (string s)

-- | Convert a paragraph into a 'Chunk'. The resulting chunk is composed by the
-- words of the original paragraph separated by softlines, so it will be
Expand All @@ -125,12 +133,23 @@ stringChunk s = pure (string s)
--
-- > isEmpty . paragraph = null . words
paragraph :: String -> Chunk Doc
paragraph = foldr (chunked (</>) . stringChunk) mempty
. words
paragraph = annTrace 0 "paragraph"
. foldr (chunked (</>) . stringChunk) mempty
. words

-- | Display pairs of strings in a table.
tabulate :: Int -> [(Doc, Doc)] -> Chunk Doc
tabulate _ [] = mempty
tabulate size table = pure $ vcat
tabulate _ [] = annTrace 1 "tabulate" mempty
tabulate size table = annTrace 1 "tabulate" . pure $ vcat
[ indent 2 (fillBreak size key <+> value)
| (key, value) <- table ]

-- | By default, @('chunkFlatAlt' x y)@ renders as @x@. However when 'group'ed,
-- @y@ will be preferred, with @x@ as the fallback for the case when @y@
-- doesn't fit.
chunkFlatAlt :: Chunk Doc -> Chunk Doc -> Chunk Doc
chunkFlatAlt x y = pure (flatAlt (extractChunk x) (extractChunk y))

-- | Determine if the document chunk is empty when rendered
chunkIsEffectivelyEmpty :: Chunk Doc -> Bool
chunkIsEffectivelyEmpty = maybe True isEffectivelyEmpty . unChunk
Loading

0 comments on commit ca02c8e

Please sign in to comment.