Switched autoformatter

This commit is contained in:
thepenguin 2022-10-27 12:20:36 +02:00
parent cea8d45ddd
commit 3b6daaba8e
No known key found for this signature in database
GPG Key ID: F258C8C10D060D5E

View File

@ -1,45 +1,46 @@
module Main where module Main where
import Control.Applicative hiding (some) import Control.Applicative hiding (some)
import Control.Monad import Control.Monad
import Data.Functor import Data.Functor
import Data.Void import Data.Void
import System.Environment import System.Environment
import System.Exit import System.Exit
import Text.Megaparsec hiding (satisfy) import Text.Megaparsec hiding (satisfy)
import Text.Megaparsec.Char import Text.Megaparsec.Char
type Parser = Parsec Void String type Parser = Parsec Void String
parseHelper :: Parser String -> String -> String parseHelper :: Parser String -> String -> String
parseHelper parser x = case parse parser "" x of parseHelper parser x = case parse parser "" x of
Left bundle -> error $ errorBundlePretty bundle Left bundle -> error $ errorBundlePretty bundle
Right text -> text Right text -> text
parseFile :: String -> String parseFile :: String -> String
parseFile = unlines . map (parseHelper fileParser) . lines parseFile = unlines . map (parseHelper fileParser) . lines
fileParser :: Parser String fileParser :: Parser String
fileParser = undefined fileParser = try $
string "* " <|>
string "** "
parseCli :: [String] -> IO String parseCli :: [String] -> IO String
parseCli [] = return usage parseCli [] = return usage
parseCli [x] = parseCli [x] =
if head x /= '-' if head x /= '-'
then parseFile <$> readFile x then parseFile <$> readFile x
else return $ useArgs $ parseHelper argParse x else return $ useArgs $ parseHelper argParse x
parseCli [x, _] = return $ useArgs $ parseHelper argParse x parseCli [x, _] = return $ useArgs $ parseHelper argParse x
parseCli _ = fail "Too many arugemnts" parseCli _ = fail "Too many arugemnts"
argParse :: Parser String argParse :: Parser String
argParse = argParse = string "-" >> some alphaNumChar
string "-" >> some alphaNumChar
useArgs :: String -> String useArgs :: String -> String
useArgs [] = "" useArgs [] = ""
useArgs ('h' : _) = usage useArgs ('h' : _) = usage
useArgs ('v' : _) = version useArgs ('v' : _) = version
useArgs (_ : xs) = useArgs xs useArgs (_ : xs) = useArgs xs
usage :: String usage :: String
usage = "Usage: otm [-hv] [file]" usage = "Usage: otm [-hv] [file]"