@@ -48,8 +48,9 @@ import System.Environment ( getArgs, getProgName )
48
48
import System.Exit ( ExitCode (.. ), exitSuccess )
49
49
import System.FilePath
50
50
import System.Console.GetOpt
51
+ import qualified Data.Set as Set
51
52
import Data.Char ( toLower , toUpper )
52
- import Data.List ( delete , intercalate , isPrefixOf , isSuffixOf , sort )
53
+ import Data.List ( intercalate , isPrefixOf , isSuffixOf , sort )
53
54
import System.Directory ( getAppUserDataDirectory , findExecutable ,
54
55
doesFileExist , Permissions (.. ), getPermissions )
55
56
import System.IO ( stdout , stderr )
@@ -88,10 +89,7 @@ copyrightMessage = intercalate "\n" [
88
89
compileInfo :: String
89
90
compileInfo =
90
91
" \n Compiled with texmath " ++
91
- VERSION_texmath ++ " , highlighting-kate " ++ VERSION_highlighting_kate ++
92
- " .\n Syntax highlighting is supported for the following languages:\n " ++
93
- wrapWords 4 78
94
- [map toLower l | l <- languages, l /= " Alert" && l /= " Alert_indent" ]
92
+ VERSION_texmath ++ " , highlighting-kate " ++ VERSION_highlighting_kate
95
93
96
94
-- | Converts a list of strings into a single string with the items printed as
97
95
-- comma separated words in lines with a maximum line length.
@@ -158,6 +156,16 @@ externalFilter f args' d = do
158
156
filterException e = err 83 $ " Error running filter " ++ f ++ " \n " ++
159
157
show e
160
158
159
+ highlightingStyles :: [(String , Style )]
160
+ highlightingStyles =
161
+ [(" pygments" , pygments),
162
+ (" tango" , tango),
163
+ (" espresso" , espresso),
164
+ (" zenburn" , zenburn),
165
+ (" kate" , kate),
166
+ (" monochrome" , monochrome),
167
+ (" haddock" , haddock)]
168
+
161
169
-- | Data structure for command line options.
162
170
data Opt = Opt
163
171
{ optTabStop :: Int -- ^ Number of spaces per tab
@@ -517,17 +525,9 @@ options =
517
525
, Option " " [" highlight-style" ]
518
526
(ReqArg
519
527
(\ arg opt -> do
520
- newStyle <- case map toLower arg of
521
- " pygments" -> return pygments
522
- " tango" -> return tango
523
- " espresso" -> return espresso
524
- " zenburn" -> return zenburn
525
- " kate" -> return kate
526
- " monochrome" -> return monochrome
527
- " haddock" -> return haddock
528
- _ -> err 39 $
529
- " Unknown style :" ++ arg
530
- return opt{ optHighlightStyle = newStyle })
528
+ case lookup (map toLower arg) highlightingStyles of
529
+ Just s -> return opt{ optHighlightStyle = s }
530
+ Nothing -> err 39 $ " Unknown style: " ++ arg)
531
531
" STYLE" )
532
532
" " -- "Style for highlighted code"
533
533
@@ -918,11 +918,56 @@ options =
918
918
let allopts = unwords (concatMap optnames options)
919
919
UTF8. hPutStrLn stdout $ printf tpl allopts
920
920
(unwords (map fst readers))
921
- (unwords (" pdf " : map fst writers))
921
+ (unwords (map fst writers))
922
922
ddir
923
923
exitSuccess ))
924
924
" " -- "Print bash completion script"
925
925
926
+ , Option " " [" list-input-formats" ]
927
+ (NoArg
928
+ (\ _ -> do
929
+ let readers'names = sort (map fst readers)
930
+ mapM_ (UTF8. hPutStrLn stdout) readers'names
931
+ exitSuccess ))
932
+ " "
933
+
934
+ , Option " " [" list-output-formats" ]
935
+ (NoArg
936
+ (\ _ -> do
937
+ let writers'names = sort (map fst writers)
938
+ mapM_ (UTF8. hPutStrLn stdout) writers'names
939
+ exitSuccess ))
940
+ " "
941
+
942
+ , Option " " [" list-extensions" ]
943
+ (NoArg
944
+ (\ _ -> do
945
+ let showExt x = drop 4 (show x) ++
946
+ if x `Set.member` pandocExtensions
947
+ then " +"
948
+ else " -"
949
+ mapM_ (UTF8. hPutStrLn stdout . showExt)
950
+ ([minBound .. maxBound ] :: [Extension ])
951
+ exitSuccess ))
952
+ " "
953
+
954
+ , Option " " [" list-highlight-languages" ]
955
+ (NoArg
956
+ (\ _ -> do
957
+ let langs = [map toLower l | l <- languages,
958
+ l /= " Alert" && l /= " Alert_indent" ]
959
+ mapM_ (UTF8. hPutStrLn stdout) langs
960
+ exitSuccess ))
961
+ " "
962
+
963
+ , Option " " [" list-highlight-styles" ]
964
+ (NoArg
965
+ (\ _ -> do
966
+ mapM_ (UTF8. hPutStrLn stdout) $
967
+ map fst highlightingStyles
968
+ exitSuccess ))
969
+ " "
970
+
926
971
, Option " v" [" version" ]
927
972
(NoArg
928
973
(\ _ -> do
@@ -961,17 +1006,7 @@ readMetaValue s = case decode (UTF8.fromString s) of
961
1006
962
1007
-- Returns usage message
963
1008
usageMessage :: String -> [OptDescr (Opt -> IO Opt )] -> String
964
- usageMessage programName = usageInfo
965
- (programName ++ " [OPTIONS] [FILES]" ++ " \n Input formats: " ++
966
- wrapWords 16 78 readers'names ++
967
- ' \n ' : replicate 16 ' ' ++
968
- " [* only Pandoc's JSON version of native AST]" ++ " \n Output formats: " ++
969
- wrapWords 16 78 writers'names ++
970
- ' \n ' : replicate 16 ' ' ++
971
- " [** for pdf output, use latex or beamer and -o FILENAME.pdf]\n Options:" )
972
- where
973
- writers'names = sort $ " json*" : " pdf**" : delete " json" (map fst writers)
974
- readers'names = sort $ " json*" : delete " json" (map fst readers)
1009
+ usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]" )
975
1010
976
1011
-- Determine default reader based on source file extensions
977
1012
defaultReaderName :: String -> [FilePath ] -> String
0 commit comments