module PFile.Completion
( profileNames
, profiles
) where
import qualified PFile.Env as Env
import PFile.Profile (Profile)
import qualified PFile.Profile as Profile
import Protolude
profileNames :: IO [[Char]]
profileNames :: IO [[Char]]
profileNames = IO [Profile]
profiles IO [Profile] -> ([Profile] -> [[Char]]) -> IO [[Char]]
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Profile -> [Char]) -> [Profile] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> [Char]
forall a b. ConvertText a b => a -> b
toS (Text -> [Char]) -> (Profile -> Text) -> Profile -> [Char]
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)
profiles :: IO [Profile]
profiles :: IO [Profile]
profiles = do
Env
env <- Options -> IO Env
forall (m :: * -> *). MonadIO m => Options -> m Env
Env.resolve Env.Options {verbose :: Bool
Env.verbose = Bool
False}
ListOptions -> ReaderT Env (ExceptT ListError IO) [Profile]
forall (m :: * -> *).
(MonadReader Env m, MonadError ListError m, MonadIO m) =>
ListOptions -> m [Profile]
Profile.list ListOptions
listOptions
ReaderT Env (ExceptT ListError IO) [Profile]
-> (ReaderT Env (ExceptT ListError IO) [Profile]
-> ExceptT ListError IO [Profile])
-> ExceptT ListError IO [Profile]
forall a b. a -> (a -> b) -> b
& (ReaderT Env (ExceptT ListError IO) [Profile]
-> Env -> ExceptT ListError IO [Profile])
-> Env
-> ReaderT Env (ExceptT ListError IO) [Profile]
-> ExceptT ListError IO [Profile]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ReaderT Env (ExceptT ListError IO) [Profile]
-> Env -> ExceptT ListError IO [Profile]
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT Env
env
ExceptT ListError IO [Profile]
-> (ExceptT ListError IO [Profile]
-> IO (Either ListError [Profile]))
-> IO (Either ListError [Profile])
forall a b. a -> (a -> b) -> b
& ExceptT ListError IO [Profile] -> IO (Either ListError [Profile])
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
runExceptT IO (Either ListError [Profile])
-> (Either ListError [Profile] -> IO [Profile]) -> IO [Profile]
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ListError -> IO [Profile])
-> ([Profile] -> IO [Profile])
-> Either ListError [Profile]
-> IO [Profile]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (IO [Profile] -> ListError -> IO [Profile]
forall a b. a -> b -> a
const (IO [Profile] -> ListError -> IO [Profile])
-> IO [Profile] -> ListError -> IO [Profile]
forall a b. (a -> b) -> a -> b
$ [Profile] -> IO [Profile]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []) [Profile] -> IO [Profile]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
where
listOptions :: Profile.ListOptions
listOptions :: ListOptions
listOptions = Profile.ListOptions {shouldFilterDangling :: Bool
Profile.shouldFilterDangling = Bool
True}