1 {-# LANGUAGE OverloadedStrings #-}
2 {-# LANGUAGE TypeApplications #-}
3 module Symantic.CLI.Test where
5 -- import Data.Monoid (Monoid(..))
6 -- import Data.Ord (Ord(..))
7 -- import Text.Show (Show(..))
8 import Control.Monad (Monad(..))
10 import Data.Either (Either(..))
11 import Data.Function (($))
12 import Data.Functor ((<$>))
13 import Data.List.NonEmpty (NonEmpty(..))
14 import Data.Maybe (Maybe(..))
15 import Data.Semigroup (Semigroup(..))
16 import Data.String (String)
17 import Data.Void (Void)
18 import Text.Show (Show(..))
19 import qualified Data.Set as Set
20 import qualified Data.Text.Lazy.IO as TL
21 import qualified Language.Symantic.Document.Term as Doc
22 import qualified Language.Symantic.Document.Term.IO as DocIO
23 import qualified System.IO as IO
24 import qualified Text.Megaparsec as P
26 import Symantic.CLI.Sym
27 import qualified Symantic.CLI.Plain as Plain
28 import qualified Symantic.CLI.Help as Help
29 import qualified Symantic.CLI.Read as Read
33 { command_source_output :: [String]
34 , command_source_format :: String
35 , command_source_dump_tct :: Bool
38 { command_compile_output :: [String]
39 , command_compile_lang :: String
40 , command_compile_dump_tct :: Bool
41 , command_compile_dump_dtc :: Bool
44 { command_schema_output :: [String]
56 Plain.Plain d (Exit d) t a -> d
60 help_usage :: Plain.Doc d => Help.Help d (Exit d) t a -> d
61 help_usage = Help.help "USAGE" "COMMAND" "OPTION" Help.defReader
62 { Help.reader_command_indent = 4 }
65 help_usage :: Plain.Doc d => Help.Help d (Exit d) t a -> d
66 help_usage = Help.textHelp Help.defReader
75 , Sym_Permutation repr
81 ) => Hdoc d repr where
82 hdoc :: repr (Exit d) ArgCommand Command
84 help_words "technical document compiler\n(disclaimer: expect hdoc's documentation to be quite… technical :)" $
85 main "hdoc" $ opts **> cmds
90 <<$? option_help (help_usage hdoc)
91 <<|?>> ((), long "version" $ exit Exit_Version)
97 help_words :: String -> repr (Exit d) t a -> repr (Exit d) t a
98 help_words d = help @d (Plain.words d)
100 option_help :: d -> ((), repr (Exit d) ArgOption ())
101 option_help d = ((), opt (OptionName 'h' "help") $ exit $ Exit_Help d)
103 command_source :: repr (Exit d) ArgCommand Command
105 help_words "Format a TCT source file." $
109 <<$? option_help (help_usage command_source)
112 <<|?>> option_dump_tct
113 command_compile :: repr (Exit d) ArgCommand Command
115 help_words "Compile a TCT source file." $
117 (\cmd os -> case cmd of
118 Command_Compile{..} -> Command_Compile{command_compile_output=command_compile_output<>os, ..}
127 <<$? option_help (help_usage command_compile)
130 <<|?>> option_dump_tct
131 <<|?>> option_dump_dtc
132 inps = many $ string "file"
133 command_schema :: repr (Exit d) ArgCommand Command
135 help_words "Show the schema for DTC documents." $
139 <<$? option_help (help_usage command_schema)
142 end_options :: repr (Exit d) ArgOption ()
144 help_words "Force the end of options.\nUseful if <file> has the same name as an option." $
147 option_lang :: (String, repr (Exit d) ArgOption String)
151 help_words ("Use language <lang>.\nDefault <lang> is: "<>def) $
154 rule_output :: repr (Exit d) ArgOption String
158 option_output :: repr (Exit d) ArgOption String
160 help_words "Output into <file>.\nDefault <file> is: input <file> whose extension is replaced by <format> here and then." $
161 opt (OptionName 'o' "output") $
163 option_dump_tct :: (Bool, repr (Exit d) ArgOption Bool)
166 help_words "Dump TCT." $
169 option_dump_dtc :: (Bool, repr (Exit d) ArgOption Bool)
172 help_words "Dump DTC." $
175 option_format :: repr (Exit d) ArgOption String
177 help_words "Output format." $
178 opt (OptionName 'f' "format") $
179 "plain" <$$ tag "plain" <||>
180 "html5" <$$ tag "html5"
181 instance Plain.Doc d => Hdoc d (Plain.Plain d)
182 instance Plain.Doc d => Hdoc d Read.Parser
183 -- instance Plain.Doc d => Hdoc d (Help.Help d)
184 instance Plain.Doc d => Hdoc d (Help.Help d)
188 [String] -> IO.IO (Maybe (Either (Exit d) Command))
190 case Read.readArgs hdoc $ Read.Args $ Read.Arg <$> as of
191 Right a -> return $ Just $ Right a
193 case P.bundleErrors errs of
194 P.TrivialError o us es :| _ -> do
195 IO.putStr $ P.parseErrorPretty @Read.Args @Void $
196 P.TrivialError o us es
198 P.FancyError _o es :| _ ->
199 case Set.toList es of
200 [P.ErrorCustom (Read.ErrorRead e)] ->
201 return $ Just $ Left e
204 parseIO :: [String] -> IO.IO ()
211 Just (Left err) -> do
214 DocIO.runTermIO IO.stdout $
215 Doc.withBreakable (Just 80) d <>
218 TL.putStrLn "version"