module System.Process.Quick.Predicate where import Control.Monad.Writer.Strict import System.Process.Quick.Prelude refinErr :: (Predicate p a, Show a) => a -> Refined p a refinErr :: forall {k} (p :: k) a. (Predicate p a, Show a) => a -> Refined p a refinErr a v = case a -> Either RefineException (Refined p a) forall {k} (p :: k) x. Predicate p x => x -> Either RefineException (Refined p x) refine a v of Left RefineException e -> Text -> Refined p a forall a t. (HasCallStack, IsText t) => t -> a error (Text -> Refined p a) -> Text -> Refined p a forall a b. (a -> b) -> a -> b $ Text "Satisfing value [" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> a -> Text forall b a. (Show a, IsString b) => a -> b show a v Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "] is no valid: " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> RefineException -> Text forall b a. (Show a, IsString b) => a -> b show RefineException e Right Refined p a vv -> Refined p a vv type ArgCollector m = (MonadIO m, MonadWriter [FilePath] m) => forall v. Data v => v -> m v class RefinedInArgLocator x where locateRefinedInArg :: Proxy x -> ArgCollector m class RefinedOutArgLocator x where locateRefinedOutArg :: Proxy x -> ArgCollector m