{-# LANGUAGE PartialTypeSignatures #-} module OurPrelude ( (>>>), (<|>), (<>), (<&>), (&), module Control.Error, module Control.Monad.Except, module Control.Monad.Trans.Class, module Control.Monad.IO.Class, module Data.Bifunctor, module System.Process.Typed, module Polysemy, module Polysemy.Error, Set, Text, Vector, interpolate, tshow, tryIOTextET, whenM, ourReadProcess_, ourReadProcess_Sem, ourReadProcessInterleaved_, ourReadProcessInterleavedBS_, ourReadProcessInterleaved, ourReadProcessInterleaved_Sem, ourReadProcessInterleavedSem, silently, bytestringToText, ) where import Control.Applicative ((<|>)) import Control.Category ((>>>)) import Control.Error import Control.Monad.Except import Control.Monad.IO.Class import Control.Monad.Trans.Class import Data.Bifunctor import qualified Data.ByteString.Lazy as BSL import Data.Function ((&)) import Data.Functor ((<&>)) import Data.Set (Set) import Data.Text (Text, pack) import qualified Data.Text.Encoding as T import qualified Data.Text.Encoding.Error as T import Data.Vector (Vector) import Language.Haskell.TH.Quote import qualified NeatInterpolation import Polysemy import Polysemy.Error hiding (note, try, tryJust) import qualified Process as P import System.Exit import System.Process.Typed interpolate :: QuasiQuoter interpolate :: QuasiQuoter interpolate = QuasiQuoter NeatInterpolation.text tshow :: Show a => a -> Text tshow :: a -> Text tshow = a -> String forall a. Show a => a -> String show (a -> String) -> (String -> Text) -> a -> Text forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> String -> Text pack tryIOTextET :: MonadIO m => IO a -> ExceptT Text m a tryIOTextET :: IO a -> ExceptT Text m a tryIOTextET = IO a -> ExceptT SomeException m a forall (m :: * -> *) a. MonadIO m => IO a -> ExceptT SomeException m a syncIO (IO a -> ExceptT SomeException m a) -> (ExceptT SomeException m a -> ExceptT Text m a) -> IO a -> ExceptT Text m a forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> (SomeException -> Text) -> ExceptT SomeException m a -> ExceptT Text m a forall (m :: * -> *) a b r. Functor m => (a -> b) -> ExceptT a m r -> ExceptT b m r fmapLT SomeException -> Text forall a. Show a => a -> Text tshow whenM :: Monad m => m Bool -> m () -> m () whenM :: m Bool -> m () -> m () whenM m Bool c m () a = m Bool c m Bool -> (Bool -> m ()) -> m () forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \Bool res -> Bool -> m () -> m () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when Bool res m () a bytestringToText :: BSL.ByteString -> Text bytestringToText :: ByteString -> Text bytestringToText = ByteString -> ByteString BSL.toStrict (ByteString -> ByteString) -> (ByteString -> Text) -> ByteString -> Text forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> (OnDecodeError -> ByteString -> Text T.decodeUtf8With OnDecodeError T.lenientDecode) ourReadProcessInterleavedBS_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m BSL.ByteString ourReadProcessInterleavedBS_ :: ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m ByteString ourReadProcessInterleavedBS_ = ProcessConfig stdin stdoutIgnored stderrIgnored -> IO ByteString forall (m :: * -> *) stdin stdoutIgnored stderrIgnored. MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m ByteString readProcessInterleaved_ (ProcessConfig stdin stdoutIgnored stderrIgnored -> IO ByteString) -> (IO ByteString -> ExceptT Text m ByteString) -> ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m ByteString forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> IO ByteString -> ExceptT Text m ByteString forall (m :: * -> *) a. MonadIO m => IO a -> ExceptT Text m a tryIOTextET ourReadProcess_ :: MonadIO m => ProcessConfig stdin stdout stderr -> ExceptT Text m (Text, Text) ourReadProcess_ :: ProcessConfig stdin stdout stderr -> ExceptT Text m (Text, Text) ourReadProcess_ = ProcessConfig stdin stdout stderr -> IO (ByteString, ByteString) forall (m :: * -> *) stdin stdoutIgnored stderrIgnored. MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ByteString, ByteString) readProcess_ (ProcessConfig stdin stdout stderr -> IO (ByteString, ByteString)) -> (IO (ByteString, ByteString) -> ExceptT Text m (Text, Text)) -> ProcessConfig stdin stdout stderr -> ExceptT Text m (Text, Text) forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> IO (ByteString, ByteString) -> ExceptT Text m (ByteString, ByteString) forall (m :: * -> *) a. MonadIO m => IO a -> ExceptT Text m a tryIOTextET (IO (ByteString, ByteString) -> ExceptT Text m (ByteString, ByteString)) -> (ExceptT Text m (ByteString, ByteString) -> ExceptT Text m (Text, Text)) -> IO (ByteString, ByteString) -> ExceptT Text m (Text, Text) forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> ((ByteString, ByteString) -> (Text, Text)) -> ExceptT Text m (ByteString, ByteString) -> ExceptT Text m (Text, Text) forall (m :: * -> *) a b l. Monad m => (a -> b) -> ExceptT l m a -> ExceptT l m b fmapRT (\(ByteString stdout,ByteString stderr) -> (ByteString -> Text bytestringToText ByteString stdout, ByteString -> Text bytestringToText ByteString stderr)) ourReadProcess_Sem :: Members '[P.Process] r => ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (Text, Text) ourReadProcess_Sem :: ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (Text, Text) ourReadProcess_Sem = ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (ByteString, ByteString) forall (r :: [Effect]) stdin stdout stderr. MemberWithError Process r => ProcessConfig stdin stdout stderr -> Sem r (ByteString, ByteString) P.read_ (ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (ByteString, ByteString)) -> (Sem r (ByteString, ByteString) -> Sem r (Text, Text)) -> ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (Text, Text) forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> ((ByteString, ByteString) -> (Text, Text)) -> Sem r (ByteString, ByteString) -> Sem r (Text, Text) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\(ByteString stdout,ByteString stderr) -> (ByteString -> Text bytestringToText ByteString stdout, ByteString -> Text bytestringToText ByteString stderr)) ourReadProcessInterleaved_ :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m Text ourReadProcessInterleaved_ :: ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m Text ourReadProcessInterleaved_ = ProcessConfig stdin stdoutIgnored stderrIgnored -> IO ByteString forall (m :: * -> *) stdin stdoutIgnored stderrIgnored. MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m ByteString readProcessInterleaved_ (ProcessConfig stdin stdoutIgnored stderrIgnored -> IO ByteString) -> (IO ByteString -> ExceptT Text m Text) -> ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m Text forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> IO ByteString -> ExceptT Text m ByteString forall (m :: * -> *) a. MonadIO m => IO a -> ExceptT Text m a tryIOTextET (IO ByteString -> ExceptT Text m ByteString) -> (ExceptT Text m ByteString -> ExceptT Text m Text) -> IO ByteString -> ExceptT Text m Text forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> (ByteString -> Text) -> ExceptT Text m ByteString -> ExceptT Text m Text forall (m :: * -> *) a b l. Monad m => (a -> b) -> ExceptT l m a -> ExceptT l m b fmapRT ByteString -> Text bytestringToText ourReadProcessInterleaved_Sem :: Members '[P.Process] r => ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r Text ourReadProcessInterleaved_Sem :: ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r Text ourReadProcessInterleaved_Sem = ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r ByteString forall (r :: [Effect]) stderr stdout stderr. MemberWithError Process r => ProcessConfig stderr stdout stderr -> Sem r ByteString P.readInterleaved_ (ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r ByteString) -> (Sem r ByteString -> Sem r Text) -> ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r Text forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> (ByteString -> Text) -> Sem r ByteString -> Sem r Text forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ByteString -> Text bytestringToText ourReadProcessInterleaved :: MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m (ExitCode, Text) ourReadProcessInterleaved :: ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m (ExitCode, Text) ourReadProcessInterleaved = ProcessConfig stdin stdoutIgnored stderrIgnored -> IO (ExitCode, ByteString) forall (m :: * -> *) stdin stdoutIgnored stderrIgnored. MonadIO m => ProcessConfig stdin stdoutIgnored stderrIgnored -> m (ExitCode, ByteString) readProcessInterleaved (ProcessConfig stdin stdoutIgnored stderrIgnored -> IO (ExitCode, ByteString)) -> (IO (ExitCode, ByteString) -> ExceptT Text m (ExitCode, Text)) -> ProcessConfig stdin stdoutIgnored stderrIgnored -> ExceptT Text m (ExitCode, Text) forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> IO (ExitCode, ByteString) -> ExceptT Text m (ExitCode, ByteString) forall (m :: * -> *) a. MonadIO m => IO a -> ExceptT Text m a tryIOTextET (IO (ExitCode, ByteString) -> ExceptT Text m (ExitCode, ByteString)) -> (ExceptT Text m (ExitCode, ByteString) -> ExceptT Text m (ExitCode, Text)) -> IO (ExitCode, ByteString) -> ExceptT Text m (ExitCode, Text) forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> ((ExitCode, ByteString) -> (ExitCode, Text)) -> ExceptT Text m (ExitCode, ByteString) -> ExceptT Text m (ExitCode, Text) forall (m :: * -> *) a b l. Monad m => (a -> b) -> ExceptT l m a -> ExceptT l m b fmapRT (\(ExitCode a, ByteString b) -> (ExitCode a, ByteString -> Text bytestringToText ByteString b)) ourReadProcessInterleavedSem :: Members '[P.Process] r => ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (ExitCode, Text) ourReadProcessInterleavedSem :: ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (ExitCode, Text) ourReadProcessInterleavedSem = ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (ExitCode, ByteString) forall (r :: [Effect]) stderr stdout stderr. MemberWithError Process r => ProcessConfig stderr stdout stderr -> Sem r (ExitCode, ByteString) P.readInterleaved (ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (ExitCode, ByteString)) -> (Sem r (ExitCode, ByteString) -> Sem r (ExitCode, Text)) -> ProcessConfig stdin stdoutIgnored stderrIgnored -> Sem r (ExitCode, Text) forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> ((ExitCode, ByteString) -> (ExitCode, Text)) -> Sem r (ExitCode, ByteString) -> Sem r (ExitCode, Text) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (\(ExitCode a, ByteString b) -> (ExitCode a, ByteString -> Text bytestringToText ByteString b)) silently :: ProcessConfig stdin stdout stderr -> ProcessConfig () () () silently :: ProcessConfig stdin stdout stderr -> ProcessConfig () () () silently = StreamSpec 'STOutput () -> ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout () forall stderr stdin stdout stderr0. StreamSpec 'STOutput stderr -> ProcessConfig stdin stdout stderr0 -> ProcessConfig stdin stdout stderr setStderr StreamSpec 'STOutput () forall (anyStreamType :: StreamType). StreamSpec anyStreamType () closed (ProcessConfig stdin stdout stderr -> ProcessConfig stdin stdout ()) -> (ProcessConfig stdin stdout () -> ProcessConfig () () ()) -> ProcessConfig stdin stdout stderr -> ProcessConfig () () () forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> StreamSpec 'STInput () -> ProcessConfig stdin stdout () -> ProcessConfig () stdout () forall stdin stdin0 stdout stderr. StreamSpec 'STInput stdin -> ProcessConfig stdin0 stdout stderr -> ProcessConfig stdin stdout stderr setStdin StreamSpec 'STInput () forall (anyStreamType :: StreamType). StreamSpec anyStreamType () closed (ProcessConfig stdin stdout () -> ProcessConfig () stdout ()) -> (ProcessConfig () stdout () -> ProcessConfig () () ()) -> ProcessConfig stdin stdout () -> ProcessConfig () () () forall k (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c >>> StreamSpec 'STOutput () -> ProcessConfig () stdout () -> ProcessConfig () () () forall stdout stdin stdout0 stderr. StreamSpec 'STOutput stdout -> ProcessConfig stdin stdout0 stderr -> ProcessConfig stdin stdout stderr setStdout StreamSpec 'STOutput () forall (anyStreamType :: StreamType). StreamSpec anyStreamType () closed