{-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} module Main (main) where import qualified OpenTimestampsClient as OTC import Options.Applicative ( Parser , command , execParser , fullDesc , help , helper , info , long , metavar , progDesc , short , some , strArgument , subparser , switch , (<**>) ) calendarUrls :: [String] calendarUrls = [ "https://a.pool.opentimestamps.org" , "https://b.pool.opentimestamps.org" , "https://a.pool.eternitywall.com" , "https://ots.btc.catallaxy.com" ] data GlobalOptions where GlobalOptions :: {globalVerbose :: Bool} -> GlobalOptions verboseOption :: Parser Bool verboseOption = switch ( long "verbose" <> short 'v' <> help "Enable verbose output" ) globalOptionsParser :: Parser GlobalOptions globalOptionsParser = GlobalOptions <$> verboseOption -- TODO Add GitExtract (?) to Extract timestamp for a single file from a timestamp git commit data Command where Info :: FilePath -> Command Prune :: FilePath -> Command Stamp :: [FilePath] -> Command Upgrade :: FilePath -> Command Verify :: FilePath -> Command infoParser :: Parser Command infoParser = Info <$> strArgument ( metavar "FILE" <> help "Timestamp file (.ots)" ) pruneParser :: Parser Command pruneParser = Prune <$> strArgument ( metavar "FILE" <> help "[TODO] Timestamp file (.ots)" ) stampParser :: Parser Command stampParser = Stamp <$> some ( strArgument ( metavar "FILE" <> help "File(s) to timestamp" ) ) upgradeParser :: Parser Command upgradeParser = Upgrade <$> strArgument ( metavar "FILE" <> help "[TODO] Timestamp file (.ots)" ) verifyParser :: Parser Command verifyParser = Verify <$> strArgument ( metavar "FILE" <> help "Timestamp file (.ots)" ) commandParser :: Parser Command commandParser = subparser ( command "info" (info infoParser (progDesc "Show information on a timestamp")) <> command "prune" (info pruneParser (progDesc "Prune timestamp")) <> command "stamp" (info stampParser (progDesc "Timestamp file(s)")) <> command "upgrade" ( info upgradeParser (progDesc "Upgrade remote calendar timestamps to be locally verifiable") ) <> command "verify" (info verifyParser (progDesc "Verify a timestamp")) ) data AppParser where AppParser :: GlobalOptions -> Command -> AppParser appParser :: Parser AppParser appParser = AppParser <$> globalOptionsParser <*> commandParser -- | Main entry point of the application. main :: IO () main = do AppParser gOpts cmd <- execParser (info (appParser <**> helper) (fullDesc <> progDesc "OpenTimestamps client")) run gOpts cmd where run :: GlobalOptions -> Command -> IO () run _gOpts (Info path) = do -- putStrLn $ "Getting info for: " ++ path OTC.info path run gOpts (Prune path) = do OTC.prune (globalVerbose gOpts) path [""] [""] -- TODO verify- and discard args run gOpts (Stamp paths) = do OTC.stamp (globalVerbose gOpts) paths calendarUrls run gOpts (Upgrade path) = do OTC.upgrade (globalVerbose gOpts) path run gOpts (Verify path) = do OTC.verify (globalVerbose gOpts) path