diff --git a/com.oracle.truffle.r.test.packages/r/install.cache.R b/com.oracle.truffle.r.test.packages/r/install.cache.R
index 9572fac20932c27f3dd1ba5d68509bb813b8a19c..864e74424d59702461b9c9880c74be0fb47d8c7f 100644
--- a/com.oracle.truffle.r.test.packages/r/install.cache.R
+++ b/com.oracle.truffle.r.test.packages/r/install.cache.R
@@ -26,10 +26,18 @@ is.fastr <- function() {
 }
 
 # A simple log function; to be replaced by a user of this file.
-log.message <- function(..., level=0) {
-    cat(..., "\n")
+log.message <- if(!exists("log.message")) {
+    function(..., level=0) {
+        if(level == 0 || verbose) {
+            cat(paste0(..., "\n"))
+        }
+    }
+} else {
+    log.message
 }
 
+
+
 pkg.cache.install <- function(pkg.cache.env, pkgname, pkg.version, lib.install, install.cmd) {
     pkg <- list(Package=pkgname, Version=pkg.version)
     is.cached <- pkg.cache.get(pkg.cache.env, pkg, lib.install)
diff --git a/com.oracle.truffle.r.test.packages/r/install.package.R b/com.oracle.truffle.r.test.packages/r/install.package.R
deleted file mode 100644
index 3101fe12946b4318b7d2b088ed538e47c332d661..0000000000000000000000000000000000000000
--- a/com.oracle.truffle.r.test.packages/r/install.package.R
+++ /dev/null
@@ -1,89 +0,0 @@
-#
-# Copyright (c) 2015, 2017, Oracle and/or its affiliates. All rights reserved.
-# DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
-#
-# This code is free software; you can redistribute it and/or modify it
-# under the terms of the GNU General Public License version 2 only, as
-# published by the Free Software Foundation.
-#
-# This code is distributed in the hope that it will be useful, but WITHOUT
-# ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
-# FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License
-# version 2 for more details (a copy is included in the LICENSE file that
-# accompanied this code).
-#
-# You should have received a copy of the GNU General Public License version
-# 2 along with this work; if not, write to the Free Software Foundation,
-# Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA.
-#
-# Please contact Oracle, 500 Oracle Parkway, Redwood Shores, CA 94065 USA
-# or visit www.oracle.com if you need additional information or have any
-# questions.
-#
-
-# A script to do a single package installation (+dependents), called from install.packages.R.
-# It exists as a separate script only to avoid internal FastR errors from killing the
-# entire installation process for multiple package installation tests.
-
-# args:
-# pkgname, contriburl, lib, pkg.cache.enabled [, api.version, cache.dir ]
-
-
-log.message <- function(..., level=0L) {
-    # TODO: verbosity
-    if (level == 0L) {
-        cat(..., "\n")
-    }
-}
-
-args <- commandArgs(TRUE)
-
-parse.args <- function() {
-	if (length(args)) {
-		pkgname <<- args[[1]]
-		contriburl <<- strsplit(args[[2]], ",")[[1]]
-		lib.install <<- args[[3]]
-
-        pkg.cache <<- as.environment(list(enabled=FALSE, table.file.name="version.table", size=2L))
-        pkg.cache$enabled <- as.logical(args[[4]])
-        cat("system.install, cache enabled: ", pkg.cache$enabled, "\n")
-        if (pkg.cache$enabled) {
-		    pkg.cache$version <- args[[5]]
-		    pkg.cache$dir <- args[[6]]
-        }
-	}
-}
-
-# return code: sucess == 0L, error == 1L
-run <- function() {
-    parse.args()
-    pkg.cache.internal.install(pkg.cache, pkgname, contriburl, lib.install)
-}
-
-# Determines the directory of the script assuming that there is a "--file=" argument on the command line.
-getCurrentScriptDir <- function() {
-     cmdArgs <- commandArgs()
-     res <- startsWith(cmdArgs, '--file=')
-     fileArg <- cmdArgs[res]
-     if (length(fileArg) > 0L) {
-         p <- strsplit(fileArg, "=")[[1]][[2]]
-         dirname(p)
-     } else {
-        NULL
-     }
-}
-
-# load package cache code
-curScriptDir <- getCurrentScriptDir()
-if (!is.null(curScriptDir)) {
-    source(file.path(curScriptDir, "install.cache.R"))
-} else {
-    log.message("Cannot use package cache since script directory cannot be determined")
-    pkg.cache.get <<- function(...) FALSE
-    pkg.cache.insert <<- function(...) FALSE
-}
-
-if (!interactive()) {
-	status.code <- run()
-    quit(status = status.code)
-}
diff --git a/com.oracle.truffle.r.test.packages/r/install.packages.R b/com.oracle.truffle.r.test.packages/r/install.packages.R
index f16cc75830be5e09ccd97c5a74b767e5bdc58ced..f4f129b0dd1253ed32436d9747d7f1e2d51d4b82 100644
--- a/com.oracle.truffle.r.test.packages/r/install.packages.R
+++ b/com.oracle.truffle.r.test.packages/r/install.packages.R
@@ -164,6 +164,19 @@ choice.depends <- function(pkg, choice=c("direct","suggests")) {
 	unname(all.deps)
 }
 
+# provides JVM args when running the tests
+fastr.test.jvm.args <- function() {
+    mx.args.file <- "com.oracle.truffle.r.test.packages/test.mx.args"
+    tryCatch({
+        if (file.exists(mx.args.file)) {
+            opts <- paste0('"', paste0("--Ja @", readLines(mx.args.file), collapse=" "), '"')
+            log.message(paste0("MX_R_GLOBAL_ARGS=", opts), level=1)
+            return (opts)
+	    }
+    })
+    return ("'--Ja @-DR:+IgnoreGraphicsCalls'")
+}
+
 # returns a vector of package names that are the direct dependents of pkg
 direct.depends <- function(pkg) {
 	choice.depends(pkg, "direct")
@@ -513,7 +526,7 @@ install.pkgs <- function(pkgnames, dependents.install=F, log=T) {
 	for (pkgname in pkgnames) {
 		if (log) {
 		    cat("BEGIN processing:", pkgname, "\n")
-            cat("timestamp: ", Sys.time(), "\n")
+            log.timestamp()
 		}
 		dependent.install.ok <- T
 		if (install.dependents.first && !dependents.install) {
@@ -563,7 +576,7 @@ install.pkgs <- function(pkgnames, dependents.install=F, log=T) {
 				}
 				if (should.install) {
 					cat("installing:", pkgname, "(", install.count, "of", install.total, ")", "\n")
-                    cat("timestamp: ", Sys.time(), "\n")
+                    log.timestamp()
 					this.result <- install.pkg(pkgname)
 					result <- result && this.result
 					if (dependents.install && !this.result) {
@@ -673,7 +686,7 @@ do.it <- function() {
 
 	if (install) {
 		cat("BEGIN package installation\n")
-        cat("timestamp: ", Sys.time(), "\n")
+        log.timestamp()
 		install.pkgs(test.pkgnames)
 		cat("END package installation\n")
 		show.install.status(test.pkgnames)
@@ -696,12 +709,12 @@ do.it <- function() {
 
 		# need to install the Suggests packages as they may be used
 		cat('BEGIN suggests install\n')
-        cat("timestamp: ", Sys.time(), "\n")
+        log.timestamp()
 		install.suggests(test.pkgnames)
 		cat('END suggests install\n')
 
 		cat("BEGIN package tests\n")
-        cat("timestamp: ", Sys.time(), "\n")
+        log.timestamp()
 		test.count = 1
 		test.total = length(test.pkgnames)
 		for (pkgname in test.pkgnames) {
@@ -741,26 +754,16 @@ fastr_error_log_size <- function() {
 # installs a single package or retrieves it from the cache
 install.pkg <- function(pkgname) {
 	error_log_size <- fastr_error_log_size()
-	if (run.mode == "system") {
-        tryCatch(
-                 system.install(pkgname)
-        , error = function(e) {
-            log.message(e$message)
-            1L
-        }, warning = function(e) {
-            log.message(e$message)
-            # According to the documentation of 'system2', a warning will provide a status field.
-            e$status
-        })
-	} else if (run.mode == "internal") {
-        pkg.cache.internal.install(pkg.cache.env=pkg.cache, pkgname=pkgname, lib.install=lib.install)
-	} else if (run.mode == "context") {
-		stop("context run-mode not implemented\n")
-	}
-	rc <- installed.ok(pkgname, error_log_size)
-	names(rc) <- pkgname
-	install.status <<- append(install.status, rc)
-	return(rc)
+    rc <- pkg.cache.internal.install(pkg.cache, pkgname, contrib.url(getOption("repos"), "source")[[1]], lib.install)
+    success <- FALSE
+    if (rc == 0L) {
+        # be paranoid and also check file system and log
+	    success <- installed.ok(pkgname, error_log_size)
+    } 	
+    log.message(paste0("installation succeeded for ", pkgname, ": ", success), level=1)
+    names(success) <- pkgname
+	install.status <<- append(install.status, success)
+	return(success)
 }
 
 # when testing under graalvm, fastr is not built so we must use the (assumed) sibling gnur repo
@@ -787,21 +790,6 @@ gnu_rscript <- function() {
 	}
 }
 
-system.install <- function(pkgname) {
-	script <- normalizePath("com.oracle.truffle.r.test.packages/r/install.package.R")
-	if (is.fastr()) {
-		rscript = file.path(R.home(), "bin", "Rscript")
-	} else {
-		rscript = gnu_rscript()
-	}
-    args <- c(script, pkgname, paste0(contrib.url(getOption("repos"), "source"), collapse=","), lib.install, as.character(pkg.cache$enabled))
-    if (pkg.cache$enabled) {
-         args <- c(args, pkg.cache$version, pkg.cache$dir)
-    } 	
-    rc <- system2(rscript, args)
-	rc
-}
-
 check.create.dir <- function(name) {
 	if (!file.exists(name)) {
 		if (!dir.create(name)) {
@@ -849,7 +837,12 @@ system.test <- function(pkgname) {
 	# we want to stop tests that hang, but some packages have many tests
 	# each of which spawns a sub-process (over which we have no control)
 	# so we time out the entire set after 20 minutes.
-	rc <- system2(rscript, args, env=c("FASTR_PROCESS_TIMEOUT=20", paste0("R_LIBS_USER=",shQuote(lib.install)),"R_LIBS="))
+    env <- c("FASTR_PROCESS_TIMEOUT=20", 
+             paste0("R_LIBS_USER=", shQuote(lib.install)),
+             "R_LIBS=",
+             paste0("MX_R_GLOBAL_ARGS=", fastr.test.jvm.args())
+            )
+	rc <- system2(rscript, args, env=env)
 	rc
 }
 
@@ -998,7 +991,13 @@ cat.args <- function() {
 
 log.message <- function(..., level=0) {
     if(level == 0 || verbose) {
-        cat(..., "\n")
+        cat(paste0(..., "\n"))
+    }
+}
+
+log.timestamp <- function() {
+    if(!quiet) {
+        cat("timestamp:", as.character(Sys.time()), "\n")
     }
 }
 
diff --git a/com.oracle.truffle.r.test.packages/test.mx.args b/com.oracle.truffle.r.test.packages/test.mx.args
new file mode 100644
index 0000000000000000000000000000000000000000..987728a589bffaabcf879ba6ce25492a0497f674
--- /dev/null
+++ b/com.oracle.truffle.r.test.packages/test.mx.args
@@ -0,0 +1,2 @@
+-DR:+IgnoreGraphicsCalls
+-DR:-EmitTmpSource
diff --git a/com.oracle.truffle.r.test.packages/test.output.filter b/com.oracle.truffle.r.test.packages/test.output.filter
new file mode 100644
index 0000000000000000000000000000000000000000..59adb8fb32082852c7596df9f9b2317c64a58ced
--- /dev/null
+++ b/com.oracle.truffle.r.test.packages/test.output.filter
@@ -0,0 +1,36 @@
+# Specify output filters for R package testing
+# 
+# Format (EBNF, sed-like action syntax): 
+# filter = pkg_pattern '=>' action .
+# pkg_pattern = <REGEX>.
+# action = command '/' string ['/' string ].
+# command = 'd' | 'D' | 'r' | 'R'
+# string = <unquoted string, slashed must be escaped with backslash>
+# 
+# Command description:
+#   d   delete exact match of the specified string (i.e. replace by empty string)
+#   D   delete line containing the specified string
+#   r   replace exact match of the first argument by the second argument
+#   R   replace line containing the first argument by the second argument
+#
+# NOTES:
+# The definition order of the filters (in this file) matters. 
+# They will be applied in order.
+#
+
+
+# for all packages: replace 'fastr' by '<engine>'
+.* => r/fastr/<engine>
+
+# for all packages: replace 'gnur' by '<engine>'
+.* => r/gnur/<engine>
+
+# for all packages: unify line containing 'RUNIT TEST PROTOCOL'
+.* => R/RUNIT TEST PROTOCOL -- /RUNIT TEST PROTOCOL -- <date_time>
+
+# for all packages: delete line containing 'Press return for next page...'
+.* => D/Press return for next page...
+
+# for all packages: delete line containing 'detaching ‘package:grid’'
+.* => D/detaching ‘package:grid’
+
diff --git a/mx.fastr/mx_fastr_pkgs.py b/mx.fastr/mx_fastr_pkgs.py
index 19ae1e189629b7368e730365126cd3e97a49f0a6..2646e04d6a3b393984cf3b41bd0fee59765e85d4 100644
--- a/mx.fastr/mx_fastr_pkgs.py
+++ b/mx.fastr/mx_fastr_pkgs.py
@@ -41,6 +41,7 @@ import mx
 import mx_fastr
 
 quiet = False
+verbose = 0
 graalvm = None
 
 def _fastr_suite_dir():
@@ -190,6 +191,7 @@ def pkgtest(args):
         --no-install             Do not install any packages (can only test installed packages).
         --list-versions          List packages to be installed/tested without installing/testing them.
         --pkg-pattern PATTERN    A regular expression to match packages.
+        --verbose, -v            Verbose output.
 
     Return codes:
         0: success
@@ -205,6 +207,12 @@ def pkgtest(args):
     if "--quiet" in args:
         global quiet
         quiet = True
+    if "-v" in args or "--verbose" in args:
+        global verbose
+        verbose = 1
+    elif "-V" in args:
+        global verbose
+        verbose = 2
 
     install_args = list(args)
 
@@ -485,12 +493,22 @@ def _set_test_status(fastr_test_info):
             with open(fastr_testfile_status.abspath) as f:
                 fastr_content = f.readlines()
 
+            # parse custom filters from file
+            filters = _select_filters(_parse_filter_file(os.path.join(_packages_test_project_dir(), "test.output.filter")), pkg)
+
             # first, parse file and see if a known test framework has been used
-            ok, skipped, failed = handle_output_file(fastr_content)
+            ok, skipped, failed = handle_output_file(fastr_testfile_status.abspath, fastr_content)
             if ok is not None:
                 fastr_testfile_status.report = ok, skipped, failed
+                # If a test framework is used, also parse the summary generated by GnuR to compare numbers.
+                gnur_ok, gnur_skipped, gnur_failed = handle_output_file(gnur_testfile_status.abspath, gnur_content)
+                total_fastr = ok + skipped + failed
+                total_gnur = gnur_ok + gnur_skipped + gnur_failed
+                if total_fastr != total_gnur:
+                    mx.log("Different number of tests executed. FastR = {} vs. GnuR = {}".format(total_fastr, total_gnur))
+                    fastr_testfile_status.status = "FAILED"
             else:
-                result, n_tests_passed, n_tests_failed = _fuzzy_compare(gnur_content, fastr_content, gnur_testfile_status.abspath, fastr_testfile_status.abspath)
+                result, n_tests_passed, n_tests_failed = _fuzzy_compare(gnur_content, fastr_content, gnur_testfile_status.abspath, fastr_testfile_status.abspath, custom_filters=filters)
                 if result == -1:
                     print "{0}: content malformed: {1}".format(pkg, gnur_test_output_relpath)
                     fastr_test_status.status = "INDETERMINATE"
@@ -540,22 +558,26 @@ def _set_test_status(fastr_test_info):
         print 'END checking ' + pkg
 
 
-def handle_output_file(test_output_file_contents):
+def handle_output_file(test_output_file, test_output_file_contents):
     """
     R package tests are usually distributed over several files. Each file can be interpreted as a test suite.
     This function parses the output file of all test suites and tries to detect if it used the testthat or RUnit.
     In this case, it parses the summary (number of passed, skipped, failed tests) of these test frameworks.
     If none of the frameworks is used, it performs an output diff and tries to determine, how many statements
     produces different output, i.e., every statement is considered to be a unit test.
-    :param test_output_file_contents: the lines of the output file
-    :return: A 3-tuple with the number of passed, skipped, and failed tests.
+    Returns a 3-tuple with the number of passed, skipped, and failed tests.
     """
+    mx.logv("Detecting output type of {!s}".format(test_output_file))
     for i in range(0, len(test_output_file_contents)):
-        if test_output_file_contents[i].startswith("testthat results"):
-            return _parse_testthat_result(test_output_file_contents, i)
-
-        # TODO parse RUnit test protocol
-
+        try:
+            if "testthat results" in test_output_file_contents[i]:
+                mx.log("Detected testthat summary in {!s}".format(test_output_file))
+                return _parse_testthat_result(test_output_file_contents, i)
+            elif "RUNIT TEST PROTOCOL" in test_output_file_contents[i]:
+                mx.log("Detected RUNIT test protocol in {!s}".format(test_output_file))
+                return _parse_runit_result(test_output_file_contents, i)
+        except BaseException as e:
+            mx.log("Error parsing test framework summary: " + str(e))
     # if this test did not use one of the known test frameworks, take the report from the fuzzy compare
     return None, None, None
 
@@ -576,6 +598,7 @@ def _parse_testthat_result(lines, i):
             return (_testthat_parse_part(ok_part), _testthat_parse_part(skipped_part), _testthat_parse_part(failed_part))
         raise Exception("Could not parse testthat status line {0}".format(result_line))
 
+
 def _testthat_parse_part(part):
     '''
     parses a part like "OK: 2"
@@ -587,6 +610,26 @@ def _testthat_parse_part(part):
     raise Exception("could not parse testthat status part {0}".format(part))
 
 
+def _parse_runit_result(lines, line_idx):
+    '''
+    RUNIT TEST PROTOCOL -- Thu Feb 08 10:54:42 2018
+    ***********************************************
+    Number of test functions: 20
+    Number of errors: 0
+    Number of failures: 0
+    '''
+    tests_total = 0
+    tests_failed = 0
+    for i in range(line_idx, len(lines)):
+        split_line = lines[i].split(":")
+        if len(split_line) >= 2:
+            if "Number of test functions" in split_line[0]:
+                tests_total = int(split_line[1])
+            elif "Number of errors" in split_line[0] or "Number of failures" in split_line[0]:
+                tests_failed = tests_failed + int(split_line[1])
+    return (tests_total - tests_failed, 0, tests_failed)
+
+
 def _find_start(content):
     marker = "Type 'q()' to quit R."
     for i in range(len(content)):
@@ -627,21 +670,28 @@ def _find_line(gnur_line, fastr_content, fastr_i):
     return -1
 
 
-def _replace_engine_references(output):
-    for idx, val in enumerate(output):
-        if "RUNIT TEST PROTOCOL -- " in val:
-            # RUnit prints the current date and time
-            output[idx] = "RUNIT TEST PROTOCOL -- <date/time>"
-        else:
-            # ignore differences which come from test directory paths
-            output[idx] = val.replace('fastr', '<engine>').replace('gnur', '<engine>')
+def _preprocess_content(output, custom_filters):
+    # load file with replacement actions
+    if custom_filters:
+        for f in custom_filters:
+            output = f.apply(output)
+    else:
+        # default builtin-filters
+        for idx, val in enumerate(output):
+            if "RUNIT TEST PROTOCOL -- " in val:
+                # RUnit prints the current date and time
+                output[idx] = "RUNIT TEST PROTOCOL -- <date_time>"
+            else:
+                # ignore differences which come from test directory paths
+                output[idx] = val.replace('fastr', '<engine>').replace('gnur', '<engine>')
+    return output
 
 
 def _is_ignored_function(fun_name, gnur_content, gnur_stmt, fastr_content, fastr_stmt):
     return gnur_stmt != -1 and fun_name in gnur_content[gnur_stmt] and fastr_stmt != -1 and fun_name in fastr_content[fastr_stmt]
 
 
-def _fuzzy_compare(gnur_content, fastr_content, gnur_filename, fastr_filename, verbose=False):
+def _fuzzy_compare(gnur_content, fastr_content, gnur_filename, fastr_filename, custom_filters=None):
     """
     Compares the test output of GnuR and FastR by ignoring implementation-specific differences like header, error,
     and warning messages.
@@ -650,8 +700,9 @@ def _fuzzy_compare(gnur_content, fastr_content, gnur_filename, fastr_filename, v
     statements passed and statements failed give the numbers on how many statements produced the same or a different
     output, respectively.
     """
-    _replace_engine_references(gnur_content)
-    _replace_engine_references(fastr_content)
+    mx.logv("Using custom filters:\n" + str(custom_filters))
+    gnur_content = _preprocess_content(gnur_content, custom_filters)
+    fastr_content = _preprocess_content(fastr_content, custom_filters)
     gnur_start = _find_start(gnur_content)
     gnur_end = _find_end(gnur_content)
     fastr_start = _find_start(fastr_content)
@@ -877,3 +928,100 @@ def computeApiChecksum(includeDir):
     hxdigest = m.hexdigest()
     mx.logv("Computed API version checksum {0}".format(hxdigest))
     return hxdigest
+
+
+class InvalidFilterException(Exception):
+    pass
+
+
+def _parse_filter(line):
+    arrow_idx = line.find("=>")
+    if arrow_idx < 0:
+        raise InvalidFilterException("cannot find separator '=>'")
+    pkg_pattern = line[:arrow_idx].strip()
+    action_str = line[arrow_idx+2:].strip()
+    action = action_str[0]
+    args = []
+    if action == "d" or action == "D":
+        # actions with one argument
+        slash_idx = action_str.find("/")
+        if slash_idx < 0:
+            raise InvalidFilterException("cannot find separator '/'")
+        args.append(action_str[slash_idx+1:])
+    elif action == "r" or action == "R":
+        # actions with two arguments
+        slash0_idx = action_str.find("/")
+        slash1_idx = action_str.find("/", slash0_idx+1)
+        if slash0_idx < 0:
+            raise InvalidFilterException("cannot find first separator '/'")
+        if slash1_idx < 0:
+            raise InvalidFilterException("cannot find second separator '/'")
+        args.append(action_str[slash0_idx + 1:slash1_idx])
+        args.append(action_str[slash1_idx + 1:])
+    return ContentFilter(pkg_pattern, action, args)
+
+
+def _parse_filter_file(file_path):
+    filters = []
+    if os.path.isfile(file_path):
+        with open(file_path) as f:
+            for linenr, line in enumerate(f.readlines()):
+                # ignore comment lines
+                if not line.startswith("#") and line.strip() != "":
+                    try:
+                        filters.append(_parse_filter(line))
+                    except InvalidFilterException as e:
+                        print "invalid filter at line {!s}: {!s}".format(linenr, e)
+
+    return filters
+
+
+class ContentFilter:
+    scope = "global"
+    pkg_pattern = "*"
+    action = "d"
+    args = []
+
+    def __init__(self, pkg_pattern, action, args):
+        self.pkg_pattern = pkg_pattern
+        self.pkg_prog = re.compile(pkg_pattern)
+        self.action = action
+        self.args = args
+
+    def _apply_to_lines(self, content, action):
+        if action is not None:
+            for idx, val in enumerate(content):
+                content[idx] = action(val)
+        return content
+
+    def apply(self, content):
+        filter_action = None
+        if self.action == "r":
+            filter_action = lambda l: l.replace(self.args[0], self.args[1])
+        elif self.action == "d":
+            filter_action = lambda l: l.replace(self.args[0], "")
+        elif self.action == "R":
+            filter_action = lambda l: self.args[1] if self.args[0] in l else l
+        elif self.action == "D":
+            filter_action = lambda l: "" if self.args[0] in l else l
+
+        return self._apply_to_lines(content, filter_action)
+
+    def applies_to_pkg(self, pkg_name):
+        return self.pkg_prog.match(pkg_name)
+
+    def __repr__(self):
+        fmt_str = "{!s} => {!s}"
+        fmt_args = [self.pkg_pattern, self.action]
+        for arg in self.args:
+            fmt_str = fmt_str + "/{!s}"
+            fmt_args.append(arg)
+        return fmt_str.format(*tuple(fmt_args))
+
+
+def _select_filters(filters, pkg):
+    pkg_filters = []
+    for f in filters:
+        if f.applies_to_pkg(pkg):
+            pkg_filters.append(f)
+    return pkg_filters