quick-process: Run external processes verified at compilation/installation

[ bsd3, library, system ] [ Propose Tags ] [ Report a vulnerability ]

The library checks program name during compilation, generates exec spec to be verified in tests, before installation or before launch.

Motivation

The strongest trait of Haskell language is its type system. This powerful type system gives infinite opportunities for experimenting with mapping relational entities onto application values in safer, more comprehensible and maintainable ways.

Compare popularity of Java and Haskell languagues and number of SOL libraries in them:

> length $ words "Hasql Beam Reigh8 postgresql-typed persistent esqueleto Opaleye Rel8 Squeal Selda Groundhog"
11
> length $ words "JPA Hibernate JOOQ EJB"
4

Haskell ecosystem counts 2.75 times more SQL libraries nonetheless according to TIOBE index in 2025 Java is 20 times more popular than Haskell and by PYPL 126 times!

As far as I remember only JOOQ resembles a type safe library. Other libraries require runtime environment to check compatibility of codebase with SQL queries.

RDBMSs talk SQL and it are inherently text oriented for extenal clients. All these Haskell libraries first of all are trying to hide plain string manipulation behind type fence as deep as possible.

Once I tried had to launch an external process in a Haskell program. Keeping in mind the 50-200x slope on SQL arena in Haskell, I expected to find at least a few libraries on hackage providing some type safety layer between my application and execv syscall interface accepting a bare strings.

The observation above motivated me experimenting with a type safe wrapper for process library.

Structure of command line arguments is way simpler than SQL. An external program can be modelled as a function with a side effect. Haskell has an amazing library for testing functions - QuickCheck including impure ones.

Main concern of external programs - they are not shipped with the application. Recall PRM hell phrase. These days situation with external explicit dependency resolution during software installation and upgrade improved by nix and bazel. Nix and bazel are powerful, because they can pack/isolate/unpack the whole dependency universe of a single app, but they are complicated systems with a steep learning curve. Plus nix is not supported on Windows. That’s why they’ve got limited popularity and lot of software is still distributed as a self-extracting archive assuming some dependencies are compatible and preinstalled manually.

Explicit list of dependencies is manually currated.

Language does not provide out of the box solution to build such list. Taking into account human factor explicit list of dependencies always has a chance to diverge from the full (effective) one. E.g. host system got newer version of dependency which behaves differently.

Software installation out of prebuilt executables usually don’t run tests.

Goals

quick-process defines following goals:

  • provide DSL for describing a call spec of an external program

  • generate types, from the call spec, compatible with application domain and arguments of an external program

  • automatic discovery of call specs in code base

  • check call spec compatibility during app development, testing and installation

  • process launch and mapping call spec to CreadeProcess

Call spec verification

Often call spec can be verified with --help key terminating command line arguments. It’s way easier than running the program in sandbox, because no files gerenration is required and validating after effects either. Help key validation support can be checked.

Examples

Constant argument

{-# LANGUAGE TemplateHaskell #-}
module CallSpecs where
import System.Process.Quick

$(genCallSpec [TrailingHelpValidate, SandboxValidate] "date" (ConstArg "+%Y" .*. HNil))
{-# LANGUAGE TemplateHaskell #-}
module CallSpecTest where

import CallSpecs
import System.Process.Quick

main :: IO ()
main = $(discoverAndVerifyCallSpecs
          (fromList [ TrailingHelpValidate
                    , SandboxValidate
                    ])
          3)
{-# LANGUAGE TemplateHaskell #-}
module Main where

import CallSpecs
import System.Process.Quick

main :: IO ()
main = callProcess Date

genCallSpec defines type Date with nullary constructor and CallSpec instance for it.

discoverAndVerifyCallSpecs discovers all types with CallSpec instances, generates 3 values per type ande executes help key check. There is not much to check besides exit code in Date spec.

callProcess is similar to callProcess from process library, but accepts typed input instead of strings.

Variable argument

{-# LANGUAGE TemplateHaskell #-}
module CallSpecs where
import System.Process.Quick

$(genCallSpec
  [TrailingHelpValidate, SandboxValidate]
  "/bin/cp"
  (   VarArg @(Refined (InFile "hs") FilePath) "source"
  .*. VarArg @(Refined (OutFile "*") FilePath) "destination"
  .*. HNil
  )
 )
{-# LANGUAGE TemplateHaskell #-}
module CallSpecTest where

import CallSpecs
import System.Process.Quick

main :: IO ()
main = $(discoverAndVerifyCallSpecs
          (fromList [ TrailingHelpValidate
                    , SandboxValidate
                    ])
          100)
{-# LANGUAGE TemplateHaskell #-}
module Main where

import CallSpecs
import System.Process.Quick

main :: IO ()
main =
  callProcess $ BinCp $(refinedTH "app.hs") $(refinedTH "app.bak")

CallSpec of cp command requires 2 parameters and here quick-process power start to show up. Refined constraint InFile ensures that first string is a valid file path to a Haskell source file. This part is delegated to refined library. HelpKey mode generates appropriate values, but they don’t point to real files on disk. Use Sandbox mode to actually launch process in a temporary dir with real files. In Sandbox OutFile cause to check that the file appears on the path once process terminates.

Subcases

Call spec can be composed of sum types.

{-# LANGUAGE TemplateHaskell #-}
module CallSpecs where
import System.Process.Quick

$(genCallSpec
  [TrailingHelpValidate, SandboxValidate]
  "find"
  (   ConstArg "."
  .*. Subcases
        "FindCases"
        [ Subcase "FindPrintf"
          (KeyArg @(Refined (Regex "^[%][fpactbnM%]$") String) "-printf" .*. HNil)
        , Subcase "FindExec"
          (KeyArg @(Refined (Regex "^(ls|file|du)$") String) "-exec" .*. ConstArg "{}" .*. ConstArg ";" .*. HNil)
        ]
  .*. HNil
  )
 )

Note usage of Regex predicate - thanks to sbv and z3 SMT solver values satisfing arbitrary TDFA regex can be generated.

Flags

Automatic Flags
NameDescriptionDefault
leafopt

Enable leaf optimization

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.0.1
Change log changelog.md
Dependencies attoparsec (>=0.14.4 && <1), base (>=4 && <5), bytestring (>=0.12.1 && <1), casing (<1), conduit (>=1.2 && <2), conduit-combinators (>=1.3.0 && <2), conduit-extra (>=1.3.6 && <2), containers (<1), deepseq (>=1.4 && <2), directory (<2), either (>=5.0.2 && <6), exceptions (>=0.6 && <1), filepath (>=1.5.2 && <2), generic-lens (>=2.2.2 && <3), generic-random (<2), hashable (>=1.0 && <2), HList (>=0.5.4.0 && <1), lens (>=5.3.2 && <6), mmorph (>=1.2.0 && <2), monad-control (>=1.0 && <2), mtl (>=2.3.1 && <3), pretty (<2), process (<2), quick-process, QuickCheck (>=2.14.3 && <3), regex-compat (<1), regex-posix (>=0.96.0 && <1), regex-tdfa (<2), relude (>=1.2.2 && <2), resourcet (>=1.1 && <2), safe-exceptions (<1), sbv (<12), semigroups (>=0.20 && <1), streaming-commons (>=0.2.2 && <1), template-haskell (<3), temporary (<2), text (>=2.0 && <3), th-utilities (<1), these-skinny (<1), time (>=1.12.2 && <2), trace-embrace (<2), transformers (>=0.6.1 && <1), transformers-base (>=0.4.6 && <1), transformers-either (>=0.1.4 && <1), unix (<3), unix-compat (>=0.4.1.1 && <1), unliftio-core (>=0.2.1 && <1) [details]
Tested with ghc ==9.10.1
License BSD-3-Clause
Copyright Daniil Iaitkov 2025
Author Daniil Iaitskov
Maintainer dyaitskov@gmail.com
Category System
Home page http://github.com/yaitskov/quick-process
Bug tracker https://github.com/yaitskov/quick-process/issues
Source repo head: git clone https://github.com/yaitskov/quick-process.git
Uploaded by DaniilIaitskov at 2025-06-01T09:30:47Z
Distributions
Downloads 3 total (3 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user
Build status unknown [no reports yet]