{-# LANGUAGE LambdaCase #-}
module Web.Browser
( openBrowser
, openBrowserWithExitCode
) where
import Control.Exception ( Exception (..), SomeException, try)
import System.Exit ( ExitCode (..) )
import qualified Web.Browser.OS as OS
openBrowser ::
String
-> IO Bool
openBrowser :: String -> IO Bool
openBrowser String
url = IO (Either SomeException (ExitCode, String, String))
tryOpenUrl IO (Either SomeException (ExitCode, String, String))
-> (Either SomeException (ExitCode, String, String) -> IO Bool)
-> IO Bool
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left SomeException
_ -> Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False
Right (ExitCode
ec, String
_, String
_) -> Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ ExitCode
ec ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
== ExitCode
ExitSuccess
where
tryOpenUrl :: IO (Either SomeException (ExitCode, String, String))
tryOpenUrl :: IO (Either SomeException (ExitCode, String, String))
tryOpenUrl = String -> IO (Either SomeException (ExitCode, String, String))
forall e.
Exception e =>
String -> IO (Either e (ExitCode, String, String))
openBrowserWithExitCode String
url
openBrowserWithExitCode ::
Exception e
=> String
-> IO (Either e (ExitCode, String, String))
openBrowserWithExitCode :: forall e.
Exception e =>
String -> IO (Either e (ExitCode, String, String))
openBrowserWithExitCode String
url = IO (ExitCode, String, String)
-> IO (Either e (ExitCode, String, String))
forall e a. Exception e => IO a -> IO (Either e a)
try (IO (ExitCode, String, String)
-> IO (Either e (ExitCode, String, String)))
-> IO (ExitCode, String, String)
-> IO (Either e (ExitCode, String, String))
forall a b. (a -> b) -> a -> b
$ String -> IO (ExitCode, String, String)
OS.openBrowserWithExitCode String
url