module Navi.Effects.MonadSystemInfo
( MonadSystemInfo (..),
)
where
import Data.Text qualified as T
import Navi.Event.Types (EventError (..))
import Navi.Prelude
import Navi.Services.Types (ServiceType (..))
import Pythia qualified
import Pythia.Data.Command (Command (..))
import Pythia.Internal.ShellApp (SimpleShell (..))
import Pythia.Internal.ShellApp qualified as ShellApp
class Monad m => MonadSystemInfo m where
query :: HasCallStack => ServiceType result -> m result
instance MonadSystemInfo IO where
query :: ServiceType result -> IO result
query :: forall result. ServiceType result -> IO result
query = \case
BatteryPercentage BatteryApp
bp ->
forall a. Text -> IO a -> IO a
rethrowPythia Text
"Battery Percentage" forall a b. (a -> b) -> a -> b
$ BatteryApp -> IO Battery
Pythia.queryBattery BatteryApp
bp
BatteryStatus BatteryApp
bp ->
forall a. Text -> IO a -> IO a
rethrowPythia Text
"Battery Status" forall a b. (a -> b) -> a -> b
$ forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view forall a. IsLabel "status" a => a
#status forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> BatteryApp -> IO Battery
Pythia.queryBattery BatteryApp
bp
NetworkInterface Device
device NetInterfaceApp
cp ->
forall a. Text -> IO a -> IO a
rethrowPythia Text
"NetInterface" forall a b. (a -> b) -> a -> b
$ Device -> NetInterfaceApp -> IO NetInterface
Pythia.queryNetInterface Device
device NetInterfaceApp
cp
Single Command
cmd -> forall a. Text -> IO a -> IO a
rethrowPythia Text
"Single" forall a b. (a -> b) -> a -> b
$ Command -> IO Text
querySingle Command
cmd
Multiple Command
cmd -> forall a. Text -> IO a -> IO a
rethrowPythia Text
"Multiple" forall a b. (a -> b) -> a -> b
$ Command -> IO Text
queryMultiple Command
cmd
{-# INLINEABLE query #-}
rethrowPythia :: Text -> IO a -> IO a
rethrowPythia :: forall a. Text -> IO a -> IO a
rethrowPythia Text
n IO a
io =
IO a
io forall (m :: Type -> Type) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
`catchAny` \SomeException
e ->
forall (m :: Type -> Type) e a.
(MonadThrow m, Exception e) =>
e -> m a
throwM forall a b. (a -> b) -> a -> b
$
MkEventError
{ $sel:name:MkEventError :: Text
name = Text
n,
$sel:short:MkEventError :: Text
short = Text
"PythiaException",
$sel:long:MkEventError :: Text
long = String -> Text
pack forall a b. (a -> b) -> a -> b
$ forall e. Exception e => e -> String
displayException SomeException
e
}
{-# INLINEABLE rethrowPythia #-}
instance MonadSystemInfo m => MonadSystemInfo (ReaderT e m) where
query :: forall result.
HasCallStack =>
ServiceType result -> ReaderT e m result
query = forall (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: Type -> Type) result.
(MonadSystemInfo m, HasCallStack) =>
ServiceType result -> m result
query
{-# INLINEABLE query #-}
queryMultiple :: Command -> IO Text
queryMultiple :: Command -> IO Text
queryMultiple Command
cmd =
let shellApp :: SimpleShell EventError Text
shellApp = Command -> SimpleShell EventError Text
multipleShellApp Command
cmd
in Text -> Text
T.strip forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall err result.
Exception err =>
SimpleShell err result -> IO result
ShellApp.runSimple SimpleShell EventError Text
shellApp
{-# INLINEABLE queryMultiple #-}
multipleShellApp :: Command -> SimpleShell EventError Text
multipleShellApp :: Command -> SimpleShell EventError Text
multipleShellApp Command
cmd =
MkSimpleShell
{ $sel:command:MkSimpleShell :: Command
command = Command
cmd,
$sel:isSupported:MkSimpleShell :: IO Bool
isSupported = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Bool
True,
$sel:parser:MkSimpleShell :: Text -> Either EventError Text
parser = Text -> Either EventError Text
parseMultiple
}
{-# INLINEABLE multipleShellApp #-}
parseMultiple :: Text -> Either EventError Text
parseMultiple :: Text -> Either EventError Text
parseMultiple = forall a b. b -> Either a b
Right
{-# INLINEABLE parseMultiple #-}
querySingle :: Command -> IO Text
querySingle :: Command -> IO Text
querySingle Command
cmd = do
let shellApp :: SimpleShell EventError Text
shellApp = Command -> SimpleShell EventError Text
singleShellApp Command
cmd
in Text -> Text
T.strip forall (f :: Type -> Type) a b. Functor f => (a -> b) -> f a -> f b
<$> forall err result.
Exception err =>
SimpleShell err result -> IO result
ShellApp.runSimple SimpleShell EventError Text
shellApp
{-# INLINEABLE querySingle #-}
singleShellApp :: Command -> SimpleShell EventError Text
singleShellApp :: Command -> SimpleShell EventError Text
singleShellApp Command
cmd =
MkSimpleShell
{ $sel:command:MkSimpleShell :: Command
command = Command
cmd,
$sel:isSupported:MkSimpleShell :: IO Bool
isSupported = forall (f :: Type -> Type) a. Applicative f => a -> f a
pure Bool
True,
$sel:parser:MkSimpleShell :: Text -> Either EventError Text
parser = Text -> Either EventError Text
parseSingle
}
{-# INLINEABLE singleShellApp #-}
parseSingle :: Text -> Either EventError Text
parseSingle :: Text -> Either EventError Text
parseSingle = forall a b. b -> Either a b
Right
{-# INLINEABLE parseSingle #-}