{-# LANGUAGE LambdaCase #-} module Imports (module Imports) where import Prelude as Imports import Data.Monoid as Imports import Data.Maybe as Imports import Control.Monad as Imports import Control.Arrow as Imports import Data.Char import System.Exit import System.Process pass :: Monad m => m () pass :: forall (m :: * -> *). Monad m => m () pass = () -> m () forall a. a -> m a forall (m :: * -> *) a. Monad m => a -> m a return () strip :: String -> String strip :: String -> String strip = String -> String forall a. [a] -> [a] reverse (String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . (Char -> Bool) -> String -> String forall a. (a -> Bool) -> [a] -> [a] dropWhile Char -> Bool isSpace (String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> String forall a. [a] -> [a] reverse (String -> String) -> (String -> String) -> String -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . (Char -> Bool) -> String -> String forall a. (a -> Bool) -> [a] -> [a] dropWhile Char -> Bool isSpace call :: FilePath -> [FilePath] -> IO () call :: String -> [String] -> IO () call String name [String] args = String -> [String] -> IO ExitCode rawSystem String name [String] args IO ExitCode -> (ExitCode -> IO ()) -> IO () forall a b. IO a -> (a -> IO b) -> IO b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \ case ExitCode ExitSuccess -> IO () forall (m :: * -> *). Monad m => m () pass ExitCode err -> ExitCode -> IO () forall a. ExitCode -> IO a exitWith ExitCode err exec :: FilePath -> [FilePath] -> IO () exec :: String -> [String] -> IO () exec String name [String] args = String -> [String] -> IO ExitCode rawSystem String name [String] args IO ExitCode -> (ExitCode -> IO ()) -> IO () forall a b. IO a -> (a -> IO b) -> IO b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= ExitCode -> IO () forall a. ExitCode -> IO a exitWith