99-- @optparse-applicative@. I do not feel that it is worth maintaining yet
1010-- another helper package on Hackage, so I just copy the code to different
1111-- projects as required. If the library grows to a substantial size or others
12- -- with to use it, I will reconsider.
12+ -- want to use it, I will reconsider.
1313--
14- -- Revision: 2022-01-02
14+ -- Revision: 2023-05-26
1515------------------------------------------------------------------------------
1616
1717{-# LANGUAGE CPP #-}
1818{-# LANGUAGE LambdaCase #-}
1919{-# LANGUAGE TupleSections #-}
2020
21+ #if defined(MIN_VERSION_ansi_wl_pprint)
22+ #if MIN_VERSION_ansi_wl_pprint (1,0,2)
23+ {-# OPTIONS_GHC -Wno-warnings-deprecations #-}
24+ #endif
25+ #endif
26+
2127module LibOA
2228 ( -- * Options
2329 -- $Options
@@ -28,14 +34,23 @@ module LibOA
2834 -- * Help
2935 , (<||>)
3036 , section
37+ , section'
3138 , table
3239 , table_
3340 , vspace
41+ -- ** Compatibility
42+ , Doc
43+ , (<$$>)
44+ , empty
45+ , string
46+ , vcat
3447 ) where
3548
3649-- https://hackage.haskell.org/package/ansi-wl-pprint
50+ #if !MIN_VERSION_optparse_applicative (0,18,0)
3751import qualified Text.PrettyPrint.ANSI.Leijen as Doc
3852import Text.PrettyPrint.ANSI.Leijen (Doc )
53+ #endif
3954
4055-- https://hackage.haskell.org/package/base
4156import Data.List (intersperse , transpose )
@@ -50,8 +65,16 @@ import qualified Options.Applicative as OA
5065import qualified Options.Applicative.Builder.Internal as OABI
5166#endif
5267import qualified Options.Applicative.Common as OAC
68+ #if MIN_VERSION_optparse_applicative (0,18,0)
69+ import Options.Applicative.Help.Pretty (Doc )
70+ #endif
5371import qualified Options.Applicative.Types as OAT
5472
73+ -- https://hackage.haskell.org/package/prettyprinter
74+ #if MIN_VERSION_optparse_applicative (0,18,0)
75+ import qualified Prettyprinter as Doc
76+ #endif
77+
5578------------------------------------------------------------------------------
5679-- $Options
5780--
@@ -103,8 +126,12 @@ versioner verStr = OA.infoOption verStr $ mconcat
103126commands :: OA. Parser a -> [String ]
104127commands =
105128 let go _ opt = case OAT. optMain opt of
129+ #if MIN_VERSION_optparse_applicative (0,18,0)
130+ OAT. CmdReader _ cmdPs -> reverse $ fst <$> cmdPs
131+ #else
106132 OAT. CmdReader _ cmds _ -> reverse cmds
107- _otherReader -> []
133+ #endif
134+ _otherReader -> []
108135 in concat . OAC. mapParser go
109136
110137------------------------------------------------------------------------------
@@ -115,22 +142,26 @@ commands =
115142d1 <||> d2 = d1 <> Doc. line <> Doc. line <> d2
116143infixr 5 <||>
117144
118- -- | Create a section with a title and indented body
145+ -- | Create a section with a title and body indented by 2 spaces
119146section :: String -> Doc -> Doc
120- section title = (Doc. text title Doc. <$$> ) . Doc. indent 2
147+ section = section' 2
148+
149+ -- | Create a section with a title and body indented by specified spaces
150+ section' :: Int -> String -> Doc -> Doc
151+ section' numSpaces title = (string title <$$> ) . Doc. indent numSpaces
121152
122153-- | Create a table, with formatting
123154table :: Int -> [[(String , Doc -> Doc )]] -> Doc
124155table sep rows = Doc. vcat $
125- map (fromMaybe Doc. empty . foldr go Nothing . zip lengths) rows
156+ map (fromMaybe empty . foldr go Nothing . zip lengths) rows
126157 where
127158 lengths :: [Int ]
128159 lengths = map ((+) sep . maximum . map (length . fst )) $ transpose rows
129160
130161 go :: (Int , (String , Doc -> Doc )) -> Maybe Doc -> Maybe Doc
131162 go (len, (s, f)) = Just . \ case
132- Just doc -> Doc. fill len (f $ Doc. string s) <> doc
133- Nothing -> f $ Doc. string s
163+ Just doc -> Doc. fill len (f $ string s) <> doc
164+ Nothing -> f $ string s
134165
135166-- | Create a table, without formatting
136167table_ :: Int -> [[String ]] -> Doc
@@ -139,3 +170,30 @@ table_ sep = table sep . (map . map) (, id)
139170-- | Vertically space documents with blank lines between them
140171vspace :: [Doc ] -> Doc
141172vspace = mconcat . intersperse (Doc. line <> Doc. line)
173+
174+ ------------------------------------------------------------------------------
175+ -- $Compatibility
176+
177+ (<$$>) :: Doc -> Doc -> Doc
178+ #if MIN_VERSION_optparse_applicative (0,18,0)
179+ l <$$> r = l <> Doc. line <> r
180+ #else
181+ (<$$>) = (Doc. <$$>)
182+ #endif
183+
184+ empty :: Doc
185+ #if MIN_VERSION_optparse_applicative (0,18,0)
186+ empty = Doc. emptyDoc
187+ #else
188+ empty = Doc. empty
189+ #endif
190+
191+ string :: String -> Doc
192+ #if MIN_VERSION_optparse_applicative (0,18,0)
193+ string = Doc. pretty
194+ #else
195+ string = Doc. string
196+ #endif
197+
198+ vcat :: [Doc ] -> Doc
199+ vcat = Doc. vcat
0 commit comments