{- |
Module                  : Iris.Browse
Copyright               : (c) 2022 Dmitrii Kovanikov
SPDX-License-Identifier : MPL-2.0
Maintainer              : Dmitrii Kovanikov <kovanikov@gmail.com>
Stability               : Experimental
Portability             : Portable

Implements a function that opens a given file in a browser.

@since 0.0.0.0
-}
module Iris.Browse (
    openInBrowser,
    BrowseException (..),
) where

import Control.Exception (Exception, throwIO)
import System.Directory (findExecutable)
import System.Environment (lookupEnv)
import System.Info (os)
import System.Process (callCommand, showCommandForUser)

{- | Exception thrown by 'openInBrowser'.

@since 0.0.0.0
-}
newtype BrowseException
    = -- | Can't find a browser application. Stores the current OS inside.
      --
      -- @since 0.0.0.0
      BrowserNotFoundException String
    deriving stock
        ( Int -> BrowseException -> ShowS
[BrowseException] -> ShowS
BrowseException -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [BrowseException] -> ShowS
$cshowList :: [BrowseException] -> ShowS
show :: BrowseException -> [Char]
$cshow :: BrowseException -> [Char]
showsPrec :: Int -> BrowseException -> ShowS
$cshowsPrec :: Int -> BrowseException -> ShowS
Show
          -- ^ @since 0.0.0.0
        )
    deriving newtype
        ( BrowseException -> BrowseException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BrowseException -> BrowseException -> Bool
$c/= :: BrowseException -> BrowseException -> Bool
== :: BrowseException -> BrowseException -> Bool
$c== :: BrowseException -> BrowseException -> Bool
Eq
          -- ^ @since 0.0.0.0
        )
    deriving anyclass
        ( Show BrowseException
Typeable BrowseException
SomeException -> Maybe BrowseException
BrowseException -> [Char]
BrowseException -> SomeException
forall e.
Typeable e
-> Show e
-> (e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> [Char])
-> Exception e
displayException :: BrowseException -> [Char]
$cdisplayException :: BrowseException -> [Char]
fromException :: SomeException -> Maybe BrowseException
$cfromException :: SomeException -> Maybe BrowseException
toException :: BrowseException -> SomeException
$ctoException :: BrowseException -> SomeException
Exception
          -- ^ @since 0.0.0.0
        )

{- | Open a given file in a browser. The function has the following algorithm:

* Check the @BROWSER@ environment variable
* If it's not set, try to guess browser depending on OS
* If unsuccsessful, print a message

__Throws:__ 'BrowseException' if can't find a browser.

@since 0.0.0.0
-}
openInBrowser :: FilePath -> IO ()
openInBrowser :: [Char] -> IO ()
openInBrowser [Char]
file =
    [Char] -> IO (Maybe [Char])
lookupEnv [Char]
"BROWSER" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Just [Char]
browser -> [Char] -> [[Char]] -> IO ()
runCommand [Char]
browser [[Char]
file]
        Maybe [Char]
Nothing -> case [Char]
os of
            [Char]
"darwin" -> [Char] -> [[Char]] -> IO ()
runCommand [Char]
"open" [[Char]
file]
            [Char]
"mingw32" -> [Char] -> [[Char]] -> IO ()
runCommand [Char]
"cmd" [[Char]
"/c", [Char]
"start", [Char]
file]
            [Char]
curOs -> do
                Maybe [Char]
browserExe <-
                    [[Char]] -> IO (Maybe [Char])
findFirstExecutable
                        [ [Char]
"xdg-open"
                        , [Char]
"cygstart"
                        , [Char]
"x-www-browser"
                        , [Char]
"firefox"
                        , [Char]
"opera"
                        , [Char]
"mozilla"
                        , [Char]
"netscape"
                        ]
                case Maybe [Char]
browserExe of
                    Just [Char]
browser -> [Char] -> [[Char]] -> IO ()
runCommand [Char]
browser [[Char]
file]
                    Maybe [Char]
Nothing -> forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ [Char] -> BrowseException
BrowserNotFoundException [Char]
curOs

-- | Execute a command with arguments.
runCommand :: FilePath -> [String] -> IO ()
runCommand :: [Char] -> [[Char]] -> IO ()
runCommand [Char]
cmd [[Char]]
args = do
    let cmdStr :: [Char]
cmdStr = [Char] -> [[Char]] -> [Char]
showCommandForUser [Char]
cmd [[Char]]
args
    [Char] -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ [Char]
"⚙  " forall a. [a] -> [a] -> [a]
++ [Char]
cmdStr
    [Char] -> IO ()
callCommand [Char]
cmdStr

findFirstExecutable :: [FilePath] -> IO (Maybe FilePath)
findFirstExecutable :: [[Char]] -> IO (Maybe [Char])
findFirstExecutable = \case
    [] -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
    [Char]
exe : [[Char]]
exes ->
        [Char] -> IO (Maybe [Char])
findExecutable [Char]
exe forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
            Maybe [Char]
Nothing -> [[Char]] -> IO (Maybe [Char])
findFirstExecutable [[Char]]
exes
            Just [Char]
path -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just [Char]
path