diff -pruN 0.6.4-1/app/Main.hs 0.9.2-2/app/Main.hs
--- 0.6.4-1/app/Main.hs	2020-01-19 07:26:08.000000000 +0000
+++ 0.9.2-2/app/Main.hs	2021-08-31 14:04:23.000000000 +0000
@@ -1,181 +1,6 @@
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE RecordWildCards #-}
-{-# LANGUAGE BangPatterns #-}
+module Main where
 
-module Main
-  ( main
-  ) where
-
-import Control.Monad
-import Data.List (intercalate)
-import Data.Semigroup ((<>))
-import qualified Data.Set as Set
-import Data.Version (showVersion)
-import GHC.IO.Handle.FD (stdout)
-import Options.Applicative
-import Paths_tldr (version)
-import System.Directory
-import System.Environment (getArgs, getExecutablePath)
-import System.FilePath
-import System.Process.Typed
-import Tldr
-
-data TldrOpts = TldrOpts
-  { tldrAction :: TldrCommand
-  } deriving (Show)
-
-data TldrCommand
-  = UpdateIndex
-  | ViewPage ViewOptions
-             [String]
-  | About
-  deriving (Show, Eq, Ord)
-
-data ViewOptions = ViewOptions
-  { platformOption :: Maybe String
-  } deriving (Show, Eq, Ord)
-
-programOptions :: Parser TldrOpts
-programOptions =
-  (TldrOpts <$> (updateIndexCommand <|> viewPageCommand <|> aboutFlag))
-
-updateIndexCommand :: Parser TldrCommand
-updateIndexCommand =
-  flag'
-    UpdateIndex
-    (long "update" <> short 'u' <> help "Update offline cache of tldr pages")
-
-aboutFlag :: Parser TldrCommand
-aboutFlag = flag' About (long "about" <> short 'a' <> help "About this program")
-
-viewOptionsParser :: Parser ViewOptions
-viewOptionsParser = ViewOptions <$> platformFlag
-
-viewPageCommand :: Parser TldrCommand
-viewPageCommand =
-  ViewPage <$> viewOptionsParser <*>
-  some (strArgument (metavar "COMMAND" <> help "name of the command"))
-
-platformFlag :: Parser (Maybe String)
-platformFlag =
-  optional
-    (strOption
-       (long "platform" <> short 'p' <> metavar "PLATFORM" <>
-        help
-          ("Prioritize specfic platform while searching. Valid values include " <>
-           platformHelpValue)))
-  where
-    platformHelpValue :: String
-    platformHelpValue = intercalate ", " platformDirs
-
-tldrDirName :: String
-tldrDirName = "tldr"
-
-repoHttpsUrl :: String
-repoHttpsUrl = "https://github.com/tldr-pages/tldr.git"
-
-checkDirs :: [String]
-checkDirs = "common" : platformDirs
-
-platformDirs :: [String]
-platformDirs = ["linux", "osx", "windows", "sunos"]
-
-tldrInitialized :: IO Bool
-tldrInitialized = do
-  dataDir <- getXdgDirectory XdgData tldrDirName
-  let dir2 = dataDir </> "tldr"
-      pages = dataDir </> "tldr" </> "pages"
-  exists <- mapM doesDirectoryExist [dataDir, dir2, pages]
-  return $ all (== True) exists
-
-initializeTldrPages :: IO ()
-initializeTldrPages = do
-  initialized <- tldrInitialized
-  unless initialized $ do
-    dataDir <- getXdgDirectory XdgData tldrDirName
-    createDirectoryIfMissing False dataDir
-    runProcess_ $ setWorkingDir dataDir $ proc "git" ["clone", repoHttpsUrl]
-
-updateTldrPages :: IO ()
-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
-
-tldrParserInfo :: ParserInfo TldrOpts
-tldrParserInfo =
-  info
-    (helper <*> versionOption <*> programOptions)
-    (fullDesc <> progDesc "tldr Client program" <>
-     header "tldr - Simplified and community-driven man pages")
-  where
-    versionOption :: Parser (a -> a)
-    versionOption =
-      infoOption
-        (showVersion version)
-        (long "version" <> short 'v' <> help "Show version")
-
-pageExists :: FilePath -> IO (Maybe FilePath)
-pageExists fname = do
-  exists <- doesFileExist fname
-  if exists
-    then return $ Just fname
-    else return Nothing
-
-getPagePath :: String -> [String] -> IO (Maybe FilePath)
-getPagePath page platformDirs = do
-  dataDir <- getXdgDirectory XdgData tldrDirName
-  let pageDir = dataDir </> "tldr" </> "pages"
-      paths = map (\x -> pageDir </> x </> page <.> "md") platformDirs
-  foldr1 (<|>) <$> mapM pageExists paths
-
-getCheckDirs :: ViewOptions -> [String]
-getCheckDirs voptions =
-  case platformOption voptions of
-    Nothing -> checkDirs
-    Just platform -> nubOrd $ ["common", platform] <> checkDirs
-
--- | Strip out duplicates
-nubOrd :: Ord a => [a] -> [a]
-nubOrd = loop mempty
-  where
-    loop _ [] = []
-    loop !s (a:as)
-      | a `Set.member` s = loop s as
-      | otherwise = a : loop (Set.insert a s) as
-
-handleAboutFlag :: IO ()
-handleAboutFlag = do
-  path <- getExecutablePath
-  let content =
-        unlines
-          [ path <> " v" <> (showVersion version)
-          , "Copyright (C) 2017 Sibi Prabakaran"
-          , "Source available at https://github.com/psibi/tldr-hs"
-          ]
-  putStr content
-
-handleTldrOpts :: TldrOpts -> IO ()
-handleTldrOpts TldrOpts {..} = do
-  case tldrAction of
-    UpdateIndex -> updateTldrPages
-    About -> handleAboutFlag
-    ViewPage voptions pages -> do
-      let npage = intercalate "-" pages
-      fname <- getPagePath npage (getCheckDirs voptions)
-      case fname of
-        Just path -> renderPage path stdout
-        Nothing -> putStrLn ("No tldr entry for " <> (intercalate " " pages))
+import           Tldr.App                       ( appMain )
 
 main :: IO ()
-main = do
-  args <- getArgs
-  case execParserPure (prefs showHelpOnEmpty) tldrParserInfo args of
-    failOpts@(Failure _) -> handleParseResult failOpts >> return ()
-    Success opts -> handleTldrOpts opts
-    compOpts@(CompletionInvoked _) -> handleParseResult compOpts >> return ()
+main = appMain
diff -pruN 0.6.4-1/CHANGELOG.md 0.9.2-2/CHANGELOG.md
--- 0.6.4-1/CHANGELOG.md	2020-03-30 04:47:19.000000000 +0000
+++ 0.9.2-2/CHANGELOG.md	2021-10-16 04:52:51.000000000 +0000
@@ -1,3 +1,30 @@
+# 0.9.2
+
+* [Apply better coloring](https://github.com/psibi/tldr-hs/pull/43 "https://github.com/psibi/tldr-hs/pull/43")
+
+# 0.9.1
+
+* When the [`NO_COLOR`](https://no-color.org/) environment variable is set, the client will not color the output.
+* Added `--[no-]color` options which enable/disable output coloring (overrides `NO_COLOR`).
+
+# 0.9.0
+
+* When pages are updated, the client now shows the download location.
+* Add optional auto-update functionality (`--auto-update-interval`)
+
+# 0.8.0
+
+* Split the library into more parts.
+* Fix [multiple line bugs](https://github.com/psibi/tldr-hs/issues/26 "multiple line bugs")
+
+# 0.7.1
+
+* Client gives non zero exit status for non-existent pages.
+
+# 0.7.0
+
+* Make it obey --language (-L) option.
+
 # 0.6.4
 
 * Fix cabal file
diff -pruN 0.6.4-1/debian/changelog 0.9.2-2/debian/changelog
--- 0.6.4-1/debian/changelog	2020-06-17 10:34:37.000000000 +0000
+++ 0.9.2-2/debian/changelog	2022-08-02 19:10:21.000000000 +0000
@@ -1,3 +1,19 @@
+haskell-tldr (0.9.2-2) unstable; urgency=medium
+
+  [ Ilias Tsitsimpis ]
+  * Declare compliance with Debian policy 4.6.1
+
+  [ Scott Talbert ]
+  * Fix FTBFS - avoid dh-exec as it doesn't work with haskell-devscripts
+
+ -- Scott Talbert <swt@techie.net>  Tue, 02 Aug 2022 15:10:21 -0400
+
+haskell-tldr (0.9.2-1) unstable; urgency=medium
+
+  * New upstream release
+
+ -- Scott Talbert <swt@techie.net>  Sun, 19 Jun 2022 23:07:08 -0400
+
 haskell-tldr (0.6.4-1) unstable; urgency=medium
 
   * New upstream release
diff -pruN 0.6.4-1/debian/control 0.9.2-2/debian/control
--- 0.6.4-1/debian/control	2020-06-17 10:34:37.000000000 +0000
+++ 0.9.2-2/debian/control	2022-08-02 19:08:59.000000000 +0000
@@ -7,22 +7,39 @@ Rules-Requires-Root: no
 Build-Depends: debhelper (>= 10),
  haskell-devscripts-minimal | haskell-devscripts (>= 0.8),
  cdbs,
- dh-exec,
  help2man,
  ghc (>= 8.4.3),
  ghc-prof,
  libghc-ansi-terminal-dev,
  libghc-ansi-terminal-prof,
+ libghc-attoparsec-dev,
+ libghc-attoparsec-prof,
  libghc-cmark-dev,
  libghc-cmark-prof,
+ libghc-http-conduit-dev,
+ libghc-http-conduit-prof,
  libghc-optparse-applicative-dev,
+ libghc-optparse-applicative-prof,
  libghc-semigroups-dev,
- libghc-typed-process-dev,
+ libghc-semigroups-prof,
+ libghc-zip-archive-dev,
+ libghc-zip-archive-prof,
+ libghc-tasty-dev,
+ libghc-tasty-prof,
+ libghc-tasty-golden-dev,
+ libghc-tasty-golden-prof,
 Build-Depends-Indep: ghc-doc,
  libghc-ansi-terminal-doc,
+ libghc-attoparsec-doc,
  libghc-cmark-doc,
-Standards-Version: 4.5.0
+ libghc-http-conduit-doc,
+ libghc-optparse-applicative-doc,
+ libghc-semigroups-doc,
+ libghc-zip-archive-doc,
+Standards-Version: 4.6.1
 Homepage: https://github.com/psibi/tldr-hs#readme
+Vcs-Browser: https://salsa.debian.org/haskell-team/DHG_packages/tree/master/p/haskell-tldr
+Vcs-Git: https://salsa.debian.org/haskell-team/DHG_packages.git [p/haskell-tldr]
 X-Description: Haskell tldr client
  Haskell tldr client with support for updating and viewing tldr pages.
  .
diff -pruN 0.6.4-1/debian/patches/no--N.diff 0.9.2-2/debian/patches/no--N.diff
--- 0.6.4-1/debian/patches/no--N.diff	2020-06-17 10:34:37.000000000 +0000
+++ 0.9.2-2/debian/patches/no--N.diff	2022-06-20 03:16:25.000000000 +0000
@@ -1,20 +1,11 @@
 --- a/tldr.cabal
 +++ b/tldr.cabal
-@@ -65,7 +65,7 @@
-     , tldr
-     , typed-process
-   if os(linux)
--    ghc-options: -threaded -optl-pthread -rtsopts -with-rtsopts=-N
-+    ghc-options: -threaded -optl-pthread -rtsopts
-   else
-     ghc-options: -threaded -rtsopts -with-rtsopts=-N
-   default-language: Haskell2010
-@@ -77,7 +77,7 @@
+@@ -91,7 +91,7 @@ test-suite tldr-test
        Paths_tldr
    hs-source-dirs:
        test
--  ghc-options: -threaded -rtsopts -with-rtsopts=-N
-+  ghc-options: -threaded -rtsopts
+-  ghc-options: -Wall -O2 -threaded -rtsopts -with-rtsopts=-N
++  ghc-options: -Wall -O2 -threaded -rtsopts
    build-depends:
        base
      , tasty
diff -pruN 0.6.4-1/debian/patches/rename-exe 0.9.2-2/debian/patches/rename-exe
--- 0.6.4-1/debian/patches/rename-exe	1970-01-01 00:00:00.000000000 +0000
+++ 0.9.2-2/debian/patches/rename-exe	2022-08-02 19:07:31.000000000 +0000
@@ -0,0 +1,11 @@
+--- a/tldr.cabal
++++ b/tldr.cabal
+@@ -67,7 +67,7 @@ library
+     , zip-archive
+   default-language: Haskell2010
+ 
+-executable tldr
++executable tldr-hs
+   main-is: Main.hs
+   other-modules:
+       Paths_tldr
diff -pruN 0.6.4-1/debian/patches/series 0.9.2-2/debian/patches/series
--- 0.6.4-1/debian/patches/series	2018-07-04 14:04:33.000000000 +0000
+++ 0.9.2-2/debian/patches/series	2022-08-02 19:06:50.000000000 +0000
@@ -1 +1,2 @@
 no--N.diff
+rename-exe
diff -pruN 0.6.4-1/debian/rules 0.9.2-2/debian/rules
--- 0.6.4-1/debian/rules	2018-09-30 11:20:48.000000000 +0000
+++ 0.9.2-2/debian/rules	2022-08-02 19:10:21.000000000 +0000
@@ -13,5 +13,5 @@ build/tldr:: build-ghc-stamp
 install/tldr:: tldr-hs.1
 
 tldr-hs.1:
-	./dist-ghc/build/tldr/tldr --help
-	help2man -N -o $@ ./dist-ghc/build/tldr/tldr
+	./dist-ghc/build/tldr-hs/tldr-hs --help
+	help2man -N -o $@ ./dist-ghc/build/tldr-hs/tldr-hs
diff -pruN 0.6.4-1/debian/tldr.install 0.9.2-2/debian/tldr.install
--- 0.6.4-1/debian/tldr.install	2018-09-30 11:21:28.000000000 +0000
+++ 0.9.2-2/debian/tldr.install	2022-08-02 19:10:21.000000000 +0000
@@ -1,2 +1 @@
-#!/usr/bin/dh-exec
-dist-ghc/build/tldr/tldr => /usr/bin/tldr-hs
+dist-ghc/build/tldr-hs/tldr-hs usr/bin
diff -pruN 0.6.4-1/README.md 0.9.2-2/README.md
--- 0.6.4-1/README.md	2020-01-26 14:00:49.000000000 +0000
+++ 0.9.2-2/README.md	2021-08-31 14:04:23.000000000 +0000
@@ -8,6 +8,18 @@
 
 Haskell client for tldr
 
+<!-- markdown-toc start - Don't edit this section. Run M-x markdown-toc-refresh-toc -->
+**Table of Contents**
+
+- [tldr](#tldr)
+    - [Installation](#installation)
+    - [Usage](#usage)
+    - [Offline caching](#offline-caching)
+    - [Snapshot](#snapshot)
+
+<!-- markdown-toc end -->
+
+
 ## Installation
 
 See Github releases: https://github.com/psibi/tldr-hs/releases
@@ -25,16 +37,22 @@ Or
 $ tldr --help
 tldr - Simplified and community-driven man pages
 
-Usage: tldr [-v|--version] ((-u|--update) | [-p|--platform PLATFORM] COMMAND)
+Usage: tldr [-v|--version] ((-u|--update) | [-p|--platform PLATFORM]
+            [-L|--language LOCALE] COMMAND | (-a|--about))
   tldr Client program
 
 Available options:
   -h,--help                Show this help text
   -v,--version             Show version
   -u,--update              Update offline cache of tldr pages
-  -p,--platform PLATFORM   Prioritize specfic platform while searching. Valid
+  -p,--platform PLATFORM   Prioritize a specific platform while searching. Valid
                            values include linux, osx, windows, sunos
+  -L,--language LOCALE     Preferred language for the page returned
   COMMAND                  name of the command
+  -a,--about               About this program
+  --auto-update-interval DAYS
+                           Perform an automatic update if the cache is older
+                           than DAYS
 ```
 
 Or a much better example of the usage:
@@ -42,7 +60,7 @@ Or a much better example of the usage:
 ``` shellsession
 $ tldr tldr
 tldr
-Simplified man pages.More information: https://tldr.sh.
+Simplified man pages. More information: https://tldr.sh.
 
  - Get typical usages of a command (hint: this is how you got here!):
    tldr {{command}}
@@ -54,6 +72,25 @@ Simplified man pages.More information: h
    tldr {{git checkout}}
 ```
 
+## Offline caching
+
+On the first run, this program caches all available tldr pages. Since
+the number of available tldr pages rises quickly, it is recommended to
+regularly update the cache.  Such an update can be run manually with:
+
+``` shellsession
+$ tldr --update
+```
+
+Starting with version `0.9.0`, users of this client can enable automatic
+updates by running it with the option `--auto-update-interval DAYS`
+specified.  The client will then check whether the cached version of the
+tldr pages is older than `DAYS` days and perform an update in that case.
+To enable this functionality permanently, users can put the line
+`alias tldr="tldr --auto-update-interval DAYS"` in their shell
+configuration file (e.g. `.bashrc`, `.zshrc`) with the desired update
+interval specified.
+
 ## Snapshot
 
 ![tldr](https://cloud.githubusercontent.com/assets/737477/24076451/2a5a604c-0c57-11e7-9bf7-13d76e8e7f12.png)
diff -pruN 0.6.4-1/Setup.hs 0.9.2-2/Setup.hs
--- 0.6.4-1/Setup.hs	2019-09-10 05:24:14.000000000 +0000
+++ 0.9.2-2/Setup.hs	2021-08-31 14:04:23.000000000 +0000
@@ -1,2 +1,2 @@
-import Distribution.Simple
+import           Distribution.Simple
 main = defaultMain
diff -pruN 0.6.4-1/src/Tldr/App/Constant.hs 0.9.2-2/src/Tldr/App/Constant.hs
--- 0.6.4-1/src/Tldr/App/Constant.hs	1970-01-01 00:00:00.000000000 +0000
+++ 0.9.2-2/src/Tldr/App/Constant.hs	2021-08-31 14:04:23.000000000 +0000
@@ -0,0 +1,13 @@
+module Tldr.App.Constant where
+
+tldrDirName :: String
+tldrDirName = "tldr"
+
+pagesUrl :: String
+pagesUrl = "https://tldr.sh/assets/tldr.zip"
+
+checkDirs :: [String]
+checkDirs = "common" : platformDirs
+
+platformDirs :: [String]
+platformDirs = ["linux", "osx", "windows", "sunos"]
diff -pruN 0.6.4-1/src/Tldr/App/Handler.hs 0.9.2-2/src/Tldr/App/Handler.hs
--- 0.6.4-1/src/Tldr/App/Handler.hs	1970-01-01 00:00:00.000000000 +0000
+++ 0.9.2-2/src/Tldr/App/Handler.hs	2021-10-13 05:21:46.000000000 +0000
@@ -0,0 +1,170 @@
+{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE BangPatterns    #-}
+
+module Tldr.App.Handler
+  ( handleAboutFlag
+  , retriveLocale
+  , checkLocale
+  , englishViewOptions
+  , getCheckDirs
+  , pageExists
+  , getPagePath
+  , updateTldrPages
+  , handleTldrOpts
+  ) where
+
+import Data.Char (toLower)
+import Data.List (intercalate)
+import Data.Maybe (fromMaybe)
+import Data.Semigroup ((<>))
+import qualified Data.Set as Set
+import Data.Version (showVersion)
+import Data.Time.Clock
+import Control.Monad (when)
+import Options.Applicative
+import Paths_tldr (version)
+import System.Directory
+  ( XdgDirectory(..)
+  , createDirectory
+  , removePathForcibly
+  , doesFileExist
+  , doesDirectoryExist
+  , getModificationTime
+  , getXdgDirectory
+  )
+import System.Environment (lookupEnv, getExecutablePath)
+import System.Exit (exitFailure)
+import System.FilePath ((<.>), (</>))
+import System.IO (hPutStrLn, stderr, stdout)
+import Network.HTTP.Simple
+import Codec.Archive.Zip
+import Tldr
+import Tldr.App.Constant
+import Tldr.Types
+
+handleAboutFlag :: IO ()
+handleAboutFlag = do
+  path <- getExecutablePath
+  let content =
+        unlines
+          [ path <> " v" <> showVersion version
+          , "Copyright (C) 2017 Sibi Prabakaran"
+          , "Source available at https://github.com/psibi/tldr-hs"
+          ]
+  putStr content
+
+retriveLocale :: IO Locale
+retriveLocale = do
+  lang <- lookupEnv "LANG"
+  pure $ computeLocale lang
+
+checkLocale :: Locale -> Bool
+checkLocale English = True
+checkLocale _ = False
+
+englishViewOptions :: ViewOptions -> ViewOptions
+englishViewOptions xs = xs { languageOption = Just "en_US.utf8" }
+
+handleTldrOpts :: TldrOpts -> IO ()
+handleTldrOpts opts@TldrOpts {..} =
+  case tldrAction of
+    UpdateIndex -> updateTldrPages
+    About -> handleAboutFlag
+    ViewPage voptions pages -> do
+      shouldPerformUpdate <- updateNecessary opts
+      when shouldPerformUpdate updateTldrPages
+      let npage = intercalate "-" pages
+      locale <-
+        case languageOption voptions of
+          Nothing -> retriveLocale
+          Just lg -> pure $ computeLocale (Just lg)
+      fname <- getPagePath locale npage (getCheckDirs voptions)
+      case fname of
+        Just path -> do
+          defColor <- getNoColorEnv
+          let color = fromMaybe defColor colorSetting
+          renderPage path stdout color
+        Nothing ->
+          if checkLocale locale
+            then do
+              hPutStrLn stderr ("No tldr entry for " <> unwords pages)
+              exitFailure
+            else handleTldrOpts
+                   (opts
+                      { tldrAction =
+                          ViewPage (englishViewOptions voptions) pages
+                      })
+
+updateNecessary :: TldrOpts -> IO Bool
+updateNecessary TldrOpts{..} = do
+  dataDir <- getXdgDirectory XdgData tldrDirName
+  dataDirExists <- doesDirectoryExist dataDir
+  if not dataDirExists
+    then return True
+    else do
+      lastCachedTime <- getModificationTime dataDir
+      currentTime <- getCurrentTime
+      let diffExceedsLimit limit
+            = currentTime `diffUTCTime` lastCachedTime
+              > fromIntegral limit * nominalDay
+      return $ maybe False diffExceedsLimit autoUpdateInterval
+
+updateTldrPages :: IO ()
+updateTldrPages = do
+  dataDir <- getXdgDirectory XdgData tldrDirName
+  removePathForcibly dataDir
+  createDirectory dataDir
+  putStrLn $ "Downloading tldr pages to " ++ dataDir
+  response <- httpLBS $ parseRequest_ pagesUrl
+  let zipArchive = toArchive $ getResponseBody response
+  extractFilesFromArchive [OptDestination dataDir] zipArchive
+
+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 other -> Unknown other
+
+getPagePath :: Locale -> String -> [String] -> IO (Maybe FilePath)
+getPagePath locale page pDirs = do
+  dataDir <- getXdgDirectory XdgData tldrDirName
+  let currentLocale = case locale of
+                        English -> "pages"
+                        Other xs -> "pages." <> xs
+                        Unknown xs -> "pages." <> xs
+                        Missing -> "pages"
+      pageDir = dataDir </> currentLocale
+      paths = map (\x -> pageDir </> x </> page <.> "md") pDirs
+  foldr1 (<|>) <$> mapM pageExists paths
+
+pageExists :: FilePath -> IO (Maybe FilePath)
+pageExists fname = do
+  exists <- doesFileExist fname
+  if exists
+    then return $ Just fname
+    else return Nothing
+
+
+getCheckDirs :: ViewOptions -> [String]
+getCheckDirs voptions =
+  case platformOption voptions of
+    Nothing -> checkDirs
+    Just platform -> nubOrd $ ["common", platform] <> checkDirs
+
+getNoColorEnv :: IO ColorSetting
+getNoColorEnv = do
+  noColorSet <- lookupEnv "NO_COLOR"
+  return $ case noColorSet of
+    Just _ -> NoColor
+    Nothing -> UseColor
+
+-- | Strip out duplicates
+nubOrd :: Ord a => [a] -> [a]
+nubOrd = loop mempty
+  where
+    loop _ [] = []
+    loop !s (a:as)
+      | a `Set.member` s = loop s as
+      | otherwise = a : loop (Set.insert a s) as
diff -pruN 0.6.4-1/src/Tldr/App.hs 0.9.2-2/src/Tldr/App.hs
--- 0.6.4-1/src/Tldr/App.hs	1970-01-01 00:00:00.000000000 +0000
+++ 0.9.2-2/src/Tldr/App.hs	2021-10-13 05:21:46.000000000 +0000
@@ -0,0 +1,105 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+
+module Tldr.App
+  ( appMain
+  ) where
+
+import Data.List (intercalate)
+import Data.Semigroup ((<>))
+import Data.Version (showVersion)
+import Options.Applicative
+import Paths_tldr (version)
+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) <*> autoUpdateIntervalOpt <*> colorFlags
+
+updateIndexCommand :: Parser TldrCommand
+updateIndexCommand =
+  flag'
+    UpdateIndex
+    (long "update" <> short 'u' <> help "Update offline cache of tldr pages")
+
+autoUpdateIntervalOpt :: Parser (Maybe Int)
+autoUpdateIntervalOpt =
+  optional
+    (option auto
+       (long "auto-update-interval" <> metavar "DAYS" <>
+        help
+          "Perform an automatic update if the cache is older than DAYS"))
+
+aboutFlag :: Parser TldrCommand
+aboutFlag = flag' About (long "about" <> short 'a' <> help "About this program")
+
+viewOptionsParser :: Parser ViewOptions
+viewOptionsParser = ViewOptions <$> platformFlag <*> languageFlag
+
+viewPageCommand :: Parser TldrCommand
+viewPageCommand =
+  ViewPage <$> viewOptionsParser <*>
+  some (strArgument (metavar "COMMAND" <> help "name of the command"))
+
+platformFlag :: Parser (Maybe String)
+platformFlag =
+  optional
+    (strOption
+       (long "platform" <> short 'p' <> metavar "PLATFORM" <>
+        help
+          ("Prioritize a specific platform while searching. Valid values include " <>
+           platformHelpValue)))
+  where
+    platformHelpValue :: String
+    platformHelpValue = intercalate ", " platformDirs
+
+languageFlag :: Parser (Maybe String)
+languageFlag =
+  optional
+    (strOption
+       (long "language" <> short 'L' <> metavar "LOCALE" <>
+        help
+          "Preferred language for the page returned"))
+
+useColorFlag :: Parser (Maybe ColorSetting)
+useColorFlag =
+  optional
+    (flag' UseColor
+        (long "color" <>
+        help
+          "Force colored output, overriding the NO_COLOR environment variable"))
+
+noColorFlag :: Parser (Maybe ColorSetting)
+noColorFlag =
+  optional
+    (flag' NoColor
+        (long "no-color" <>
+        help
+          "Disable colored output"))
+
+colorFlags :: Parser (Maybe ColorSetting)
+colorFlags = useColorFlag <|> noColorFlag
+
+tldrParserInfo :: ParserInfo TldrOpts
+tldrParserInfo =
+  info
+    (helper <*> versionOption <*> programOptions)
+    (fullDesc <> progDesc "tldr Client program" <>
+     header "tldr - Simplified and community-driven man pages")
+  where
+    versionOption :: Parser (a -> a)
+    versionOption =
+      infoOption
+        (showVersion version)
+        (long "version" <> short 'v' <> help "Show version")
+
+appMain :: IO ()
+appMain = do
+  args <- getArgs
+  case execParserPure (prefs showHelpOnEmpty) tldrParserInfo args of
+    failOpts@(Failure _) -> void $ handleParseResult failOpts
+    Success opts -> handleTldrOpts opts
+    compOpts@(CompletionInvoked _) -> void $ handleParseResult compOpts
diff -pruN 0.6.4-1/src/Tldr/Parser.hs 0.9.2-2/src/Tldr/Parser.hs
--- 0.6.4-1/src/Tldr/Parser.hs	1970-01-01 00:00:00.000000000 +0000
+++ 0.9.2-2/src/Tldr/Parser.hs	2021-10-16 04:40:18.000000000 +0000
@@ -0,0 +1,101 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE BangPatterns #-}
+
+module Tldr.Parser where
+
+import Prelude              hiding (takeWhile)
+import Control.Applicative
+import Data.Attoparsec.Combinator
+import Data.Attoparsec.Text
+import Data.Text                   (Text)
+
+import qualified Data.Text as T
+
+-- $setup
+-- >>> :set -XOverloadedStrings
+-- >>> import Data.Attoparsec.Text
+
+
+-- | Parses '{{foo}}' blocks in CommonMark Code, such that:
+--
+-- * `ls {{foo}} bar` -> `[Left "ls ", Right "foo", Left " bar"]`
+--
+-- >>> parseOnly codeParser ""
+-- Right []
+-- >>> parseOnly codeParser "tar"
+-- Right [Left "tar"]
+-- >>> parseOnly codeParser "tar{"
+-- Right [Left "tar{"]
+-- >>> parseOnly codeParser "tar{{"
+-- Right [Left "tar{{"]
+-- >>> parseOnly codeParser "tar{{{"
+-- Right [Left "tar{{{"]
+-- >>> parseOnly codeParser "tar}"
+-- Right [Left "tar}"]
+-- >>> parseOnly codeParser "tar{{{b}"
+-- Right [Left "tar{{{b}"]
+-- >>> parseOnly codeParser "tar{{{b}}"
+-- Right [Left "tar",Right "{b"]
+-- >>> parseOnly codeParser "tar{{b}}}"
+-- Right [Left "tar",Right "b}"]
+-- >>> parseOnly codeParser "tar xf {{source.tar[.gz|.bz2|.xz]}} --directory={{directory}}"
+-- Right [Left "tar xf ",Right "source.tar[.gz|.bz2|.xz]",Left " --directory=",Right "directory"]
+codeParser :: Parser [Either Text Text]
+codeParser = collectEither <$> outer
+ where
+  inner :: Parser [Either Text Text]
+  inner = do
+    _ <- char '{'
+    _ <- char '{'
+    l <- takeWhile (/= '}')
+    e <- optional findEnd
+    case e of
+      Just e' -> (\o -> [Right (l <> e')         ] <> o) <$> (outer <|> pure [])
+      Nothing -> (\o -> [Left  (T.pack "{{" <> l)] <> o) <$> (outer <|> pure [])
+   where
+    findEnd :: Parser Text
+    findEnd = do
+      c1 <- anyChar
+      (p2, p3) <- peek2Chars
+      case (c1, p2, p3) of
+        ('}', Just '}', Just '}') -> (T.singleton '}' <>) <$> findEnd
+        ('}', Just '}', _)        -> mempty <$ anyChar
+        _                         -> fail ("Couldn't find end: " <> show (c1, p2, p3))
+
+  outer :: Parser [Either Text Text]
+  outer = do
+    o  <- takeWhile (/= '{')
+    (p1, p2) <- peek2Chars
+    case (p1, p2) of
+      (Just '{', Just '{') -> (\i   -> [Left o                   ] <> i) <$> (inner <|> ((\t -> [Left t]) <$> takeText))
+      (Just '{', _)        -> (\a b -> [Left (o <> T.singleton a)] <> b) <$> anyChar <*> outer
+      _                    -> pure [Left o]
+
+
+-- | Collect both Lefts and Rights, mappending them to zore or one item per connected sublist.
+--
+-- >>> collectEither []
+-- []
+-- >>> collectEither [Right "abc", Right "def", Left "x", Left "z", Right "end"]
+-- [Right "abcdef",Left "xz",Right "end"]
+-- >>> collectEither [Right "", Right "def", Left "x", Left "", Right ""]
+-- [Right "def",Left "x"]
+collectEither :: (Eq a, Eq b, Monoid a, Monoid b) => [Either a b] -> [Either a b]
+collectEither = go Nothing
+ where
+  go Nothing  [] = []
+  go (Just !x) []
+    | x == Right mempty || x == Left mempty = []
+    | otherwise                             = [x]
+  go Nothing           (Left  b:br) = go (Just (Left  b))        br
+  go Nothing           (Right b:br) = go (Just (Right b))        br
+  go (Just (Left !a))  (Left  b:br) = go (Just (Left (a <> b)))  br
+  go (Just (Right !a)) (Right b:br) = go (Just (Right (a <> b))) br
+  go (Just !a) xs
+    | a == Right mempty || a == Left mempty = go Nothing xs
+    | otherwise                             = a:go Nothing xs
+
+
+-- | Peek 2 characters, not consuming any input.
+peek2Chars :: Parser (Maybe Char, Maybe Char)
+peek2Chars = lookAhead ((,) <$> optional anyChar <*> optional anyChar)
diff -pruN 0.6.4-1/src/Tldr/Types.hs 0.9.2-2/src/Tldr/Types.hs
--- 0.6.4-1/src/Tldr/Types.hs	1970-01-01 00:00:00.000000000 +0000
+++ 0.9.2-2/src/Tldr/Types.hs	2021-10-13 05:21:46.000000000 +0000
@@ -0,0 +1,39 @@
+module Tldr.Types where
+
+import System.Console.ANSI
+
+data Locale = English | Missing | Other String | Unknown String
+
+data ColorSetting = NoColor | UseColor
+  deriving (Eq, Show, Ord, Enum, Bounded)
+
+data ConsoleSetting =
+  ConsoleSetting
+    { italic :: Bool
+    , underline :: Underlining
+    , blink :: BlinkSpeed
+    , fgIntensity :: ColorIntensity
+    , fgColor :: Color
+    , bgIntensity :: ColorIntensity
+    , consoleIntensity :: ConsoleIntensity
+    }
+
+data TldrOpts = TldrOpts
+  { tldrAction :: TldrCommand
+  , autoUpdateInterval :: Maybe Int
+  , colorSetting :: Maybe ColorSetting
+  } deriving (Show)
+
+data TldrCommand
+  = UpdateIndex
+  | ViewPage ViewOptions
+             [String]
+  | About
+  deriving (Show, Eq, Ord)
+
+data ViewOptions =
+  ViewOptions
+    { platformOption :: Maybe String
+    , languageOption :: Maybe String
+    }
+  deriving (Show, Eq, Ord)
diff -pruN 0.6.4-1/src/Tldr.hs 0.9.2-2/src/Tldr.hs
--- 0.6.4-1/src/Tldr.hs	2019-10-19 17:28:11.000000000 +0000
+++ 0.9.2-2/src/Tldr.hs	2021-10-16 04:51:41.000000000 +0000
@@ -1,4 +1,5 @@
 {-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE LambdaCase #-}
 
 module Tldr
   ( parsePage
@@ -12,23 +13,16 @@ module Tldr
   ) where
 
 import CMark
+import Control.Monad (forM_)
+import Data.Attoparsec.Text
 import Data.Monoid ((<>))
 import Data.Text hiding (cons)
-import qualified Data.Text as T
-import qualified Data.Text.IO as TIO
 import GHC.IO.Handle (Handle)
 import System.Console.ANSI
-
-data ConsoleSetting =
-  ConsoleSetting
-    { italic :: Bool
-    , underline :: Underlining
-    , blink :: BlinkSpeed
-    , fgIntensity :: ColorIntensity
-    , fgColor :: Color
-    , bgIntensity :: ColorIntensity
-    , consoleIntensity :: ConsoleIntensity
-    }
+import Tldr.Parser
+import Tldr.Types (ConsoleSetting(..), ColorSetting (..))
+import qualified Data.Text as T
+import qualified Data.Text.IO as TIO
 
 defConsoleSetting :: ConsoleSetting
 defConsoleSetting =
@@ -45,32 +39,51 @@ defConsoleSetting =
 headingSetting :: ConsoleSetting
 headingSetting = defConsoleSetting {consoleIntensity = BoldIntensity}
 
-toSGR :: ConsoleSetting -> [SGR]
-toSGR cons =
-  [ SetItalicized (italic cons)
-  , SetConsoleIntensity (consoleIntensity cons)
-  , SetUnderlining (underline cons)
-  , SetBlinkSpeed (blink cons)
-  , SetColor Foreground (fgIntensity cons) (fgColor cons)
-  ]
-
-renderNode :: NodeType -> Handle -> IO ()
-renderNode (TEXT txt) handle = TIO.hPutStrLn handle txt
-renderNode (HTML_BLOCK txt) handle = TIO.hPutStrLn handle txt
-renderNode (CODE_BLOCK _ txt) handle = TIO.hPutStrLn handle txt
-renderNode (HTML_INLINE txt) handle = TIO.hPutStrLn handle txt
-renderNode (CODE txt) handle = TIO.hPutStrLn handle ("   " <> txt)
-renderNode LINEBREAK handle = TIO.hPutStrLn handle ""
-renderNode (LIST _) handle = TIO.hPutStrLn handle "" >> TIO.hPutStr handle " - "
-renderNode _ _ = return ()
-
-changeConsoleSetting :: NodeType -> IO ()
-changeConsoleSetting (HEADING _) = setSGR $ toSGR headingSetting
-changeConsoleSetting BLOCK_QUOTE = setSGR $ toSGR headingSetting
-changeConsoleSetting ITEM = setSGR $ toSGR $ defConsoleSetting {fgColor = Green}
-changeConsoleSetting (CODE _) =
-  setSGR $ toSGR $ defConsoleSetting {fgColor = Yellow}
-changeConsoleSetting _ = return ()
+toSGR :: ColorSetting -> ConsoleSetting -> [SGR]
+toSGR color cons = case color of
+  NoColor -> def
+  UseColor -> SetColor Foreground (fgIntensity cons) (fgColor cons) : def
+  where
+    def =
+      [ SetItalicized (italic cons)
+      , SetConsoleIntensity (consoleIntensity cons)
+      , SetUnderlining (underline cons)
+      , SetBlinkSpeed (blink cons)
+      ]
+
+reset :: ColorSetting -> IO ()
+reset color = case color of
+  NoColor -> pure ()
+  UseColor -> setSGR [Reset]
+
+renderNode :: NodeType -> ColorSetting -> Handle -> IO ()
+renderNode nt@(TEXT txt) color handle = changeConsoleSetting color nt >> TIO.hPutStrLn handle (txt <> "\n") >> reset color
+renderNode nt@(HTML_BLOCK txt) color handle = changeConsoleSetting color nt >> TIO.hPutStrLn handle txt >> reset color
+renderNode nt@(CODE_BLOCK _ txt) color handle = changeConsoleSetting color nt >> TIO.hPutStrLn handle txt >> reset color
+renderNode nt@(HTML_INLINE txt) color handle = changeConsoleSetting color nt >> TIO.hPutStrLn handle txt >> reset color
+renderNode (CODE txt) color handle = renderCode color txt handle
+renderNode nt@LINEBREAK color handle = changeConsoleSetting color nt >> TIO.hPutStrLn handle "" >> reset color
+renderNode nt@(LIST _) color handle = changeConsoleSetting color nt >> TIO.hPutStrLn handle "" >> TIO.hPutStr handle " - " >> reset color
+renderNode _ _ _ = return ()
+
+renderCode :: ColorSetting -> Text -> Handle -> IO ()
+renderCode color txt handle = do
+  TIO.hPutStr handle ("   ")
+  case parseOnly codeParser txt of
+    Right xs -> do
+      forM_ xs $ \case
+        Left x -> changeConsoleSetting color (CODE txt) >> TIO.hPutStr handle x >> reset color
+        Right x -> TIO.hPutStr handle x
+    Left _ -> changeConsoleSetting color (CODE txt) >> TIO.hPutStr handle txt >> reset color
+  TIO.hPutStr handle ("\n")
+
+changeConsoleSetting :: ColorSetting -> NodeType -> IO ()
+changeConsoleSetting color (HEADING _) = setSGR $ toSGR color headingSetting
+changeConsoleSetting color BLOCK_QUOTE = setSGR $ toSGR color headingSetting
+changeConsoleSetting color ITEM = setSGR $ toSGR color $ defConsoleSetting {fgColor = Green}
+changeConsoleSetting color (CODE _) =
+  setSGR $ toSGR color $ defConsoleSetting {fgColor = Yellow}
+changeConsoleSetting _ _ = return ()
 
 handleSubsetNodeType :: NodeType -> Text
 handleSubsetNodeType (HTML_BLOCK txt) = txt
@@ -81,6 +94,7 @@ handleSubsetNodeType (CODE txt) = txt
 handleSubsetNodeType _ = mempty
 
 handleSubsetNode :: Node -> Text
+handleSubsetNode (Node _ SOFTBREAK _) = "\n"
 handleSubsetNode (Node _ ntype xs) =
   handleSubsetNodeType ntype <> T.concat (Prelude.map handleSubsetNode xs)
 
@@ -88,18 +102,17 @@ handleParagraph :: [Node] -> Handle -> I
 handleParagraph xs handle =
   TIO.hPutStrLn handle $ T.concat $ Prelude.map handleSubsetNode xs
 
-handleNode :: Node -> Handle -> IO ()
-handleNode (Node _ PARAGRAPH xs) handle = handleParagraph xs handle
-handleNode (Node _ ITEM xs) handle =
-  changeConsoleSetting ITEM >> handleParagraph xs handle
-handleNode (Node _ ntype xs) handle = do
-  changeConsoleSetting ntype
-  renderNode ntype handle
+handleNode :: Node -> Handle -> ColorSetting -> IO ()
+handleNode (Node _ PARAGRAPH xs) handle _ = handleParagraph xs handle
+handleNode (Node _ ITEM xs) handle color =
+  changeConsoleSetting color ITEM >> handleParagraph xs handle
+handleNode (Node _ ntype xs) handle color = do
+  renderNode ntype color handle
   mapM_
     (\(Node _ ntype' ns) ->
-       renderNode ntype' handle >> mapM_ (`handleNode` handle) ns)
+       renderNode ntype' color handle >> mapM_ (\n -> handleNode n handle color) ns)
     xs
-  setSGR [Reset]
+  reset color
 
 parsePage :: FilePath -> IO Node
 parsePage fname = do
@@ -107,7 +120,7 @@ parsePage fname = do
   let node = commonmarkToNode [] page
   return node
 
-renderPage :: FilePath -> Handle -> IO ()
-renderPage fname handle = do
+renderPage :: FilePath -> Handle -> ColorSetting -> IO ()
+renderPage fname handle color = do
   node <- parsePage fname
-  handleNode node handle
+  handleNode node handle color
diff -pruN 0.6.4-1/test/data/grep.golden 0.9.2-2/test/data/grep.golden
--- 0.6.4-1/test/data/grep.golden	2019-09-10 05:24:14.000000000 +0000
+++ 0.9.2-2/test/data/grep.golden	2021-10-16 04:40:18.000000000 +0000
@@ -1,26 +1,28 @@
 grep
-Matches patterns in input text.Supports simple patterns and regular expressions.
+
+Matches patterns in input text.
+Supports simple patterns and regular expressions.
 
  - Search for an exact string:
-   grep {{search_string}} {{path/to/file}}
+   grep search_string path/to/file
 
  - Search in case-insensitive mode:
-   grep -i {{search_string}} {{path/to/file}}
+   grep -i search_string path/to/file
 
  - Search recursively (ignoring non-text files) in current directory for an exact string:
-   grep -RI {{search_string}} .
+   grep -RI search_string .
 
  - Use extended regular expressions (supporting ?, +, {}, () and |):
-   grep -E {{^regex$}} {{path/to/file}}
+   grep -E ^regex$ path/to/file
 
  - Print 3 lines of [C]ontext around, [B]efore, or [A]fter each match:
-   grep -{{C|B|A}} 3 {{search_string}} {{path/to/file}}
+   grep -C|B|A 3 search_string path/to/file
 
  - Print file name with the corresponding line number for each match:
-   grep -Hn {{search_string}} {{path/to/file}}
+   grep -Hn search_string path/to/file
 
  - Use the standard input instead of a file:
-   cat {{path/to/file}} | grep {{search_string}}
+   cat path/to/file | grep search_string
 
  - Invert match for excluding specific strings:
-   grep -v {{search_string}}
+   grep -v search_string
diff -pruN 0.6.4-1/test/data/ls.golden 0.9.2-2/test/data/ls.golden
--- 0.6.4-1/test/data/ls.golden	2019-09-10 05:24:14.000000000 +0000
+++ 0.9.2-2/test/data/ls.golden	2021-08-31 14:04:23.000000000 +0000
@@ -1,4 +1,5 @@
 ls
+
 List directory contents.
 
  - List files one per line:
diff -pruN 0.6.4-1/test/data/ps.golden 0.9.2-2/test/data/ps.golden
--- 0.6.4-1/test/data/ps.golden	2019-09-10 05:24:14.000000000 +0000
+++ 0.9.2-2/test/data/ps.golden	2021-10-16 04:40:18.000000000 +0000
@@ -1,4 +1,5 @@
 ps
+
 Information about running processes.
 
  - List all running processes:
@@ -8,7 +9,7 @@ Information about running processes.
    ps auxww
 
  - Search for a process that matches a string:
-   ps aux | grep {{string}}
+   ps aux | grep string
 
  - List all processes of the current user in extra full format:
    ps --user $(id -u) -F
@@ -17,4 +18,4 @@ Information about running processes.
    ps --user $(id -u) f
 
  - Get the parent pid of a process:
-   ps -o ppid= -p {{pid}}
+   ps -o ppid= -p pid
diff -pruN 0.6.4-1/test/Spec.hs 0.9.2-2/test/Spec.hs
--- 0.6.4-1/test/Spec.hs	2019-09-10 05:24:14.000000000 +0000
+++ 0.9.2-2/test/Spec.hs	2021-10-13 05:21:46.000000000 +0000
@@ -1,4 +1,5 @@
 import Tldr
+import Tldr.Types (ColorSetting(..))
 import Test.Tasty
 import Test.Tasty.Golden (goldenVsFile)
 import System.IO (withBinaryFile, IOMode(..))
@@ -12,7 +13,7 @@ goldenTests = testGroup "Golden tests" [
 
 renderPageToFile :: FilePath -> FilePath -> IO ()
 renderPageToFile mdfile opfile = do
-  withBinaryFile opfile WriteMode (\handle -> renderPage mdfile handle)
+  withBinaryFile opfile WriteMode (\handle -> renderPage mdfile handle UseColor)
 
 -- For adding new command, you need to add:
 -- A new ".md" file for that command
@@ -27,7 +28,7 @@ commandTest str = goldenVsFile (str <> "
       md cmd = prefix <> cmd <> ".md"
 
 gtests :: TestTree
-gtests = testGroup "(render test)" 
+gtests = testGroup "(render test)"
          [
           commandTest "ls"
          , commandTest "ps"
diff -pruN 0.6.4-1/tldr.cabal 0.9.2-2/tldr.cabal
--- 0.6.4-1/tldr.cabal	2020-03-30 04:47:29.000000000 +0000
+++ 0.9.2-2/tldr.cabal	2021-10-16 04:53:41.000000000 +0000
@@ -1,13 +1,11 @@
 cabal-version: 1.12
 
--- This file has been generated from package.yaml by hpack version 0.31.2.
+-- This file has been generated from package.yaml by hpack version 0.34.4.
 --
 -- see: https://github.com/sol/hpack
---
--- hash: 6d6a28bd0b56fd00a272f305ae388900bd3a5e235b44afb32bd4e758846bf2f7
 
 name:           tldr
-version:        0.6.4
+version:        0.9.2
 synopsis:       Haskell tldr client
 description:    Haskell tldr client with support for viewing tldr pages. Has offline
                 cache for accessing pages. Visit https://tldr.sh for more details.
@@ -34,19 +32,39 @@ source-repository head
   type: git
   location: https://github.com/psibi/tldr-hs
 
+flag static
+  description: Statically link executables.
+  manual: True
+  default: False
+
 library
   exposed-modules:
       Tldr
+      Tldr.App
+      Tldr.App.Constant
+      Tldr.App.Handler
+      Tldr.Parser
+      Tldr.Types
   other-modules:
       Paths_tldr
   hs-source-dirs:
       src
+  ghc-options: -Wall -O2
   build-depends:
       ansi-terminal
+    , attoparsec
     , base >=4.7 && <5
     , bytestring
     , cmark
+    , containers
+    , directory
+    , filepath
+    , http-conduit
+    , optparse-applicative
+    , semigroups
     , text
+    , time
+    , zip-archive
   default-language: Haskell2010
 
 executable tldr
@@ -55,19 +73,15 @@ executable tldr
       Paths_tldr
   hs-source-dirs:
       app
+  ghc-options: -Wall -O2
   build-depends:
       base
-    , containers
-    , directory
-    , filepath
-    , optparse-applicative
-    , semigroups
     , tldr
-    , typed-process
-  if os(linux)
-    ghc-options: -threaded -optl-pthread -rtsopts -with-rtsopts=-N
+  if flag(static) && os(linux)
+    ghc-options: -rtsopts -threaded -optc-Os -optl=-pthread -optl=-static -fPIC
+    ld-options: -static
   else
-    ghc-options: -threaded -rtsopts -with-rtsopts=-N
+    ghc-options: -rtsopts -threaded
   default-language: Haskell2010
 
 test-suite tldr-test
@@ -77,7 +91,7 @@ test-suite tldr-test
       Paths_tldr
   hs-source-dirs:
       test
-  ghc-options: -threaded -rtsopts -with-rtsopts=-N
+  ghc-options: -Wall -O2 -threaded -rtsopts -with-rtsopts=-N
   build-depends:
       base
     , tasty
