Skip to content

Commit

Permalink
Fix hlint issues
Browse files Browse the repository at this point in the history
  • Loading branch information
psibi committed Aug 8, 2020
1 parent f5589ed commit b9f1fff
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 20 deletions.
10 changes: 5 additions & 5 deletions src/Tldr/App.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}

module Tldr.App
( appMain
Expand All @@ -14,10 +13,11 @@ import System.Environment (getArgs)
import Tldr.App.Constant (platformDirs)
import Tldr.App.Handler
import Tldr.Types
import Control.Monad (void)

programOptions :: Parser TldrOpts
programOptions =
(TldrOpts <$> (updateIndexCommand <|> viewPageCommand <|> aboutFlag))
TldrOpts <$> (updateIndexCommand <|> viewPageCommand <|> aboutFlag)

updateIndexCommand :: Parser TldrCommand
updateIndexCommand =
Expand Down Expand Up @@ -54,7 +54,7 @@ languageFlag =
(strOption
(long "language" <> short 'L' <> metavar "LOCALE" <>
help
("Preferred language for the page returned")))
"Preferred language for the page returned"))

tldrParserInfo :: ParserInfo TldrOpts
tldrParserInfo =
Expand All @@ -73,6 +73,6 @@ appMain :: IO ()
appMain = do
args <- getArgs
case execParserPure (prefs showHelpOnEmpty) tldrParserInfo args of
failOpts@(Failure _) -> handleParseResult failOpts >> return ()
failOpts@(Failure _) -> void $ handleParseResult failOpts
Success opts -> handleTldrOpts opts
compOpts@(CompletionInvoked _) -> handleParseResult compOpts >> return ()
compOpts@(CompletionInvoked _) -> void $ handleParseResult compOpts
26 changes: 12 additions & 14 deletions src/Tldr/App/Handler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,7 @@ import System.Directory
, doesFileExist
, getXdgDirectory
)
import System.Environment (getExecutablePath)
import System.Environment (lookupEnv)
import System.Environment (lookupEnv, getExecutablePath)
import System.Exit (exitFailure)
import System.FilePath ((<.>), (</>))
import System.IO (hPutStrLn, stderr, stdout)
Expand All @@ -44,7 +43,7 @@ handleAboutFlag = do
path <- getExecutablePath
let content =
unlines
[ path <> " v" <> (showVersion version)
[ path <> " v" <> showVersion version
, "Copyright (C) 2017 Sibi Prabakaran"
, "Source available at https://github.com/psibi/tldr-hs"
]
Expand All @@ -63,23 +62,23 @@ englishViewOptions :: ViewOptions -> ViewOptions
englishViewOptions xs = xs { languageOption = Just "en_US.utf8" }

handleTldrOpts :: TldrOpts -> IO ()
handleTldrOpts opts@TldrOpts {..} = do
handleTldrOpts opts@TldrOpts {..} =
case tldrAction of
UpdateIndex -> updateTldrPages
About -> handleAboutFlag
ViewPage voptions pages -> do
let npage = intercalate "-" pages
locale <-
case (languageOption voptions) of
case languageOption voptions of
Nothing -> retriveLocale
Just lg -> pure $ computeLocale (Just lg)
fname <- getPagePath locale npage (getCheckDirs voptions)
case fname of
Just path -> renderPage path stdout
Nothing -> do
Nothing ->
if checkLocale locale
then do
hPutStrLn stderr ("No tldr entry for " <> (intercalate " " pages))
hPutStrLn stderr ("No tldr entry for " <> unwords pages)
exitFailure
else handleTldrOpts
(opts
Expand All @@ -92,18 +91,17 @@ updateTldrPages = do
dataDir <- getXdgDirectory XdgData tldrDirName
let repoDir = dataDir </> "tldr"
repoExists <- doesDirectoryExist repoDir
case repoExists of
True ->
runProcess_ $
setWorkingDir (repoDir) $ proc "git" ["pull", "origin", "master"]
False -> initializeTldrPages
if repoExists
then runProcess_ $
setWorkingDir repoDir $ proc "git" ["pull", "origin", "master"]
else initializeTldrPages

computeLocale :: Maybe String -> Locale
computeLocale lang = case map toLower <$> lang of
Nothing -> Missing
Just ('e':'n':_) -> English
Just (a:b:'_':_) -> Other (a:b:[])
Just (a:b:c:'_':_) -> Other (a:b:c:[])
Just (a:b:'_':_) -> Other [a,b]
Just (a:b:c:'_':_) -> Other [a,b,c]
Just other -> Unknown other

getPagePath :: Locale -> String -> [String] -> IO (Maybe FilePath)
Expand Down
2 changes: 1 addition & 1 deletion src/Tldr/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ data ConsoleSetting =
, consoleIntensity :: ConsoleIntensity
}

data TldrOpts = TldrOpts
newtype TldrOpts = TldrOpts
{ tldrAction :: TldrCommand
} deriving (Show)

Expand Down

0 comments on commit b9f1fff

Please sign in to comment.