{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
module PFile.Main.List
( main
) where
import PFile.CLI.List (Options (..))
import PFile.Env (Env)
import PFile.Error (modifyError)
import qualified PFile.Log as Log
import qualified PFile.Profile as Profile
import Protolude
main :: (MonadReader Env m, MonadIO m) => Options -> m ()
main :: forall (m :: * -> *).
(MonadReader Env m, MonadIO m) =>
Options -> m ()
main Options {Bool
shouldFilterDangling :: Bool
shouldFilterDangling :: Options -> Bool
shouldFilterDangling} =
(Text -> m ()) -> (() -> m ()) -> Either Text () -> m ()
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either Text -> m ()
forall (m :: * -> *) a. MonadIO m => Text -> m a
Log.panic () -> m ()
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Text () -> m ())
-> (ExceptT Text m () -> m (Either Text ()))
-> ExceptT Text m ()
-> m ()
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ExceptT Text m () -> m (Either Text ())
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT (ExceptT Text m () -> m ()) -> ExceptT Text m () -> m ()
forall a b. (a -> b) -> a -> b
$
ListOptions -> ExceptT ListError (ExceptT Text m) [Profile]
forall (m :: * -> *).
(MonadReader Env m, MonadError ListError m, MonadIO m) =>
ListOptions -> m [Profile]
Profile.list ListOptions
listOptions
ExceptT ListError (ExceptT Text m) [Profile]
-> (ExceptT ListError (ExceptT Text m) [Profile]
-> ExceptT Text m [Profile])
-> ExceptT Text m [Profile]
forall a b. a -> (a -> b) -> b
& (ListError -> Text)
-> ExceptT ListError (ExceptT Text m) [Profile]
-> ExceptT Text m [Profile]
forall e2 (m :: * -> *) e1 a.
MonadError e2 m =>
(e1 -> e2) -> ExceptT e1 m a -> m a
modifyError ListError -> Text
Profile.showListError
ExceptT Text m [Profile]
-> ([Profile] -> ExceptT Text m ()) -> ExceptT Text m ()
forall a b.
ExceptT Text m a -> (a -> ExceptT Text m b) -> ExceptT Text m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Profile -> ExceptT Text m ()) -> [Profile] -> ExceptT Text m ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (Text -> ExceptT Text m ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putStrLn (Text -> ExceptT Text m ())
-> (Profile -> Text) -> Profile -> ExceptT Text m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Text
Profile.unName (Name -> Text) -> (Profile -> Name) -> Profile -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Profile -> Name
Profile.name)
where
listOptions :: Profile.ListOptions
listOptions :: ListOptions
listOptions = Profile.ListOptions {Bool
shouldFilterDangling :: Bool
shouldFilterDangling :: Bool
Profile.shouldFilterDangling}