# Shh [![](https://img.shields.io/hackage/v/shh.svg?colorB=%23999&label=shh)](http://hackage.haskell.org/package/shh) [![](https://img.shields.io/hackage/v/shh-extras.svg?colorB=%23999&label=shh-extras)](http://hackage.haskell.org/package/shh-extras) [![](https://builds.sr.ht/~lukec/shh/nix.yml.svg)](https://builds.sr.ht/~lukec/shh/nix.yml?)
Shh is a library to enable convinient shell-like programming in Haskell. It works well in scripts, and from GHCi, allowing you to use GHCi as a shell. ```haskell {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ExtendedDefaultRules #-} module Readme (test) where import Shh import Control.Concurrent.Async import Prelude hiding (head) import Test.Tasty import Test.Tasty.HUnit import Test.Tasty.QuickCheck import qualified System.Directory import qualified Data.ByteString.Lazy.Char8 as Char8 import Data.List (nub) import Data.Char load SearchPath ["echo", "base64", "cat", "head", "sleep", "mktemp", "ls", "wc", "find", "tr", "users", "sha256sum", "false", "true"] curl :: Cmd curl = true test :: IO () test = do ```
It's primary purpose is in replacing shell scripts. As such, many functions are provided to mimic the shell environment, and porting shell scripts to shh should be fairly straightforward. A simple ["cargo culting" port](docs/porting.md) should work in most situations, and perhaps be even more robust than the original. It is also a wrapper tool around launching GHCi as a shell. It supports * Automatically defining a function for each executable on your `$PATH` using template Haskell, as well as a runtime check to ensure they all exist on startup. * Redirction of stdout and stderr ```haskell -- Redirect stdout echo "Hello" &> StdErr echo "Hello" &> Truncate ".tmp_file" -- Redirect stderr echo "Hello" &!> Append "/dev/null" echo "Hello" &!> StdOut ``` * Piping stdout or stderr to the input of a chained process ```haskell cat "/dev/urandom" |> base64 |> head "-n" 5 ``` * Multiple processes sequentially feeding a single process ```haskell (echo 1 >> echo 2) |> cat ``` * Use of Haskells concurrency primitives. ```haskell race (sleep 1 >> echo "Slept for 1") (sleep 2 >> echo "Slept for 2") ``` ```haskell mapConcurrently_ (\url -> curl "-Ls" url |> wc) [ "https://raw.githubusercontent.com/luke-clifton/shh/master/shell.nix" , "https://raw.githubusercontent.com/luke-clifton/shh/master/README.md" ] ``` * Capturing of process output ```haskell s <- echo "Hello" |> tr "-d" "l" |> capture print s loggedIn <- nub . Char8.words <$> (users |> capture) putStrLn $ "Logged in users: " ++ show loggedIn mapM_ Char8.putStrLn =<< (find "-maxdepth" 1 "-print0" |> captureEndBy0) ``` * Capturing infinite output of a process lazily ```haskell cat "/dev/urandom" |> base64 |> readInput (mapM_ Char8.putStrLn . take 3 . Char8.lines) ``` * Write strings to stdin of a process. ```haskell writeOutput "Hello\n" |> cat -- Hello "Hello" >>> sha256sum sha256sum <<< "Hello" ``` * Proper exceptions, when a process exits with a failure code, an exception is thrown. You can catch these normally. The exception includes the error code, the command, and all it's arguments. ```haskell false "Ha, it died" -- *** Exception: Command `false "Ha, it died"` failed [exit 1] ``` ```haskell exitCode false -- 1 ``` * "Native" processes, i.e. Haskell functions that behave like a process. ```haskell echo "Hello" |> pureProc (Char8.map toUpper) |> tr "-d" "L" -- HEO ``` * And much, much more! Look at the documentation on Hackage for a comprehensive overview of all the possibilities. ## Mnemonics Shh has many symbols that might seem intimidating at first, but there is a simple mnemonic for them. | Piping. Looks like a pipe, same as in POSIX shells. & Redirection, think of the shell `2>&1` >,< The direction of flow of a command ! Operate on stderr instead of stdout So, for example, ls |> cat Pipe the stdout of `ls` into stdin of `cat` cat <| ls Same as above ls &> StdErr Redirect stdout of `ls` to wherever stderr is going. StdErr <& ls Same as above ls &!> StdOut Redirect stderr of `ls` to wherever stdout is going. StdOut