Blame lib/dg.exp

Packit 62fe53
# `dg' general purpose testcase driver.
Packit 62fe53
Packit 62fe53
# Copyright (C) 1992-2016 Free Software Foundation, Inc.
Packit 62fe53
#
Packit 62fe53
# This file is part of DejaGnu.
Packit 62fe53
#
Packit 62fe53
# DejaGnu is free software; you can redistribute it and/or modify it
Packit 62fe53
# under the terms of the GNU General Public License as published by
Packit 62fe53
# the Free Software Foundation; either version 3 of the License, or
Packit 62fe53
# (at your option) any later version.
Packit 62fe53
#
Packit 62fe53
# DejaGnu is distributed in the hope that it will be useful, but
Packit 62fe53
# WITHOUT ANY WARRANTY; without even the implied warranty of
Packit 62fe53
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
Packit 62fe53
# General Public License for more details.
Packit 62fe53
#
Packit 62fe53
# You should have received a copy of the GNU General Public License
Packit 62fe53
# along with DejaGnu; if not, write to the Free Software Foundation,
Packit 62fe53
# Inc., 51 Franklin Street - Fifth Floor, Boston, MA 02110-1301, USA.
Packit 62fe53
Packit 62fe53
# This file was written by Doug Evans (dje@cygnus.com).
Packit 62fe53
Packit 62fe53
# This file is based on old-dejagnu.exp.  It is intended to be more extensible
Packit 62fe53
# without incurring the overhead that old-dejagnu.exp can.  All test framework
Packit 62fe53
# commands appear in the testcase as "{ dg-xxx args ... }".  We pull them out
Packit 62fe53
# with one grep, and then run the function(s) named by "dg-xxx".  When running
Packit 62fe53
# dg-xxx, the line number that it occurs on is always passed as the first
Packit 62fe53
# argument.  We also support different kinds of tools via callbacks.
Packit 62fe53
#
Packit 62fe53
# The currently supported options are:
Packit 62fe53
#
Packit 62fe53
# dg-prms-id N
Packit 62fe53
#	set prms_id to N
Packit 62fe53
#
Packit 62fe53
# dg-options "options ..." [{ target selector }]
Packit 62fe53
#	specify special options to pass to the tool (eg: compiler)
Packit 62fe53
#
Packit 62fe53
# dg-do do-what-keyword [{ target/xfail selector }]
Packit 62fe53
#	`do-what-keyword' is tool specific and is passed unchanged to
Packit 62fe53
#	${tool}-dg-test.  An example is gcc where `keyword' can be any of:
Packit 62fe53
#	preprocess | compile | assemble | link | run
Packit 62fe53
#	and will do one of: produce a .i, produce a .s, produce a .o,
Packit 62fe53
#	produce an a.out, or produce an a.out and run it (the default is
Packit 62fe53
#	'compile').
Packit 62fe53
#
Packit 62fe53
# dg-error regexp comment [{ target/xfail selector } [{.|0|linenum}]]
Packit 62fe53
#	indicate an error message <regexp> is expected on this line
Packit 62fe53
#	(the test fails if it doesn't occur)
Packit 62fe53
#	linenum=0 for general tool messages (eg: -V arg missing).
Packit 62fe53
#	"." means the current line.
Packit 62fe53
#
Packit 62fe53
# dg-warning regexp comment [{ target/xfail selector } [{.|0|linenum}]]
Packit 62fe53
#	indicate a warning message <regexp> is expected on this line
Packit 62fe53
#	(the test fails if it doesn't occur)
Packit 62fe53
#
Packit 62fe53
# dg-bogus regexp comment [{ target/xfail selector } [{.|0|linenum}]]
Packit 62fe53
#	indicate a bogus error message <regexp> used to occur here
Packit 62fe53
#	(the test fails if it does occur)
Packit 62fe53
#
Packit 62fe53
# dg-build regexp comment [{ target/xfail selector }]
Packit 62fe53
#	indicate the build use to fail for some reason
Packit 62fe53
#	(errors covered here include bad assembler generated, tool crashes,
Packit 62fe53
#	and link failures)
Packit 62fe53
#	(the test fails if it does occur)
Packit 62fe53
#
Packit 62fe53
# dg-excess-errors comment [{ target/xfail selector }]
Packit 62fe53
#	indicate excess errors are expected (any line)
Packit 62fe53
#	(this should only be used sparingly and temporarily)
Packit 62fe53
#
Packit 62fe53
# dg-output regexp [{ target selector }]
Packit 62fe53
#	indicate the expected output of the program is <regexp>
Packit 62fe53
#	(there may be multiple occurrences of this, they are concatenated)
Packit 62fe53
#
Packit 62fe53
# dg-final { tcl script }
Packit 62fe53
#	add some Tcl script to be run at the end
Packit 62fe53
#	(there may be multiple occurrences of this, they are concatenated)
Packit 62fe53
#	(unbalanced braces must be \-escaped)
Packit 62fe53
#
Packit 62fe53
# "{ target selector }" is a list of expressions that determine whether the
Packit 62fe53
# test succeeds or fails for a particular target, or in some cases whether the
Packit 62fe53
# option applies for a particular target.  If the case of `dg-do' it specifies
Packit 62fe53
# whether the testcase is even attempted on the specified target.
Packit 62fe53
#
Packit 62fe53
# The target selector is always optional.  The format is one of:
Packit 62fe53
#
Packit 62fe53
# { xfail *-*-* ... } - the test is expected to fail for the given targets
Packit 62fe53
# { target *-*-* ... } - the option only applies to the given targets
Packit 62fe53
#
Packit 62fe53
# At least one target must be specified, use *-*-* for "all targets".
Packit 62fe53
# At present it is not possible to specify both `xfail' and `target'.
Packit 62fe53
# "native" may be used in place of "*-*-*".
Packit 62fe53
#
Packit 62fe53
# Example:
Packit 62fe53
#
Packit 62fe53
#       [ ... some complicated code ... ]
Packit 62fe53
#	return a; /* { dg-build "fatal" "ran out of spill regs" { xfail i386-*-* } } */
Packit 62fe53
#
Packit 62fe53
# In this contrived example, the compiler used to crash on the "return
Packit 62fe53
# a;" for some target and it still does crash on i386-*-*.
Packit 62fe53
#
Packit 62fe53
# ??? It might be possible to add additional optional arguments by having
Packit 62fe53
# something like: { dg-error ".*syntax.*" "syntax error" { { foo 1 } ... } }
Packit 62fe53
#
Packit 62fe53
# Callbacks
Packit 62fe53
#
Packit 62fe53
# ${tool}-dg-test testfile do-what-keyword extra-flags
Packit 62fe53
#
Packit 62fe53
#	Run the test, be it compiler, assembler, or whatever.
Packit 62fe53
#
Packit 62fe53
# ${tool}-dg-prune target_triplet text
Packit 62fe53
#
Packit 62fe53
#	Optional callback to delete output from the tool that can occur
Packit 62fe53
#	even in successful ("pass") situations and interfere with output
Packit 62fe53
#	pattern matching.  This also gives the tool an opportunity to review
Packit 62fe53
#	the output and check for any conditions which indicate an "untested"
Packit 62fe53
#	or "unresolved" state.  An example is if a testcase is too big and
Packit 62fe53
#	fills all available ram (which can happen for 16 bit CPUs).  The
Packit 62fe53
#	result is either the pruned text or
Packit 62fe53
#	"::untested|unresolved|unsupported::message"
Packit 62fe53
#	(eg: "::unsupported::memory full").
Packit 62fe53
#
Packit 62fe53
# Notes:
Packit 62fe53
# 1) All runnable testcases must return 0 from main() for success.
Packit 62fe53
#    You can't rely on getting any return code from target boards, and the
Packit 62fe53
#    `exec' command says a program fails if it returns non-zero.
Packit 62fe53
#
Packit 62fe53
# Language independence is (theoretically) achieved by:
Packit 62fe53
#
Packit 62fe53
# 1) Using global $tool to indicate the language (eg: gcc, g++, gas, etc.).
Packit 62fe53
#    This should only be used to look up other objects.  We don't want to
Packit 62fe53
#    have to add code for each new language that is supported.  If this is
Packit 62fe53
#    done right, no code needs to be added here for each new language.
Packit 62fe53
#
Packit 62fe53
# 2) Passing tool options in as arguments.
Packit 62fe53
#
Packit 62fe53
#    Earlier versions of ${tool}_start (eg: gcc_start) would only take the name
Packit 62fe53
#    of the file to compile as an argument.  Newer versions accept a list of
Packit 62fe53
#    one or two elements, the second being a string of *all* options to pass
Packit 62fe53
#    to the tool.  We require this facility.
Packit 62fe53
#
Packit 62fe53
# 3) Callbacks.
Packit 62fe53
#
Packit 62fe53
# Try not to do anything else that makes life difficult.
Packit 62fe53
#
Packit 62fe53
# The normal way to write a testsuite is to have a .exp file containing:
Packit 62fe53
#
Packit 62fe53
# load_lib ${tool}-dg.exp
Packit 62fe53
# dg-init
Packit 62fe53
# dg-runtest [lsort [glob -nocomplain $srcdir/$subdir/foo*]] ...
Packit 62fe53
# dg-finish
Packit 62fe53

Packit 62fe53
# Global state variables.
Packit 62fe53
# The defaults are for GCC.
Packit 62fe53
Packit 62fe53
# The default do-what keyword.
Packit 62fe53
set dg-do-what-default compile
Packit 62fe53
Packit 62fe53
# When dg-interpreter-batch-mode is 1, no execution test or excess error
Packit 62fe53
# tests are performed.
Packit 62fe53
set dg-interpreter-batch-mode 0
Packit 62fe53
Packit 62fe53
# Line number format.  This is how line numbers appear in program output.
Packit 62fe53
set dg-linenum-format ":%d:"
Packit 62fe53
proc dg-format-linenum { linenum } {
Packit 62fe53
    global dg-linenum-format
Packit 62fe53
    return [format ${dg-linenum-format} $linenum]
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
# Useful subroutines.
Packit 62fe53
Packit 62fe53
# dg-get-options -- pick out the dg-xxx options in a testcase
Packit 62fe53
#
Packit 62fe53
# PROG is the file name of the testcase.
Packit 62fe53
# The result is a list of options found.
Packit 62fe53
#
Packit 62fe53
# Example: For the following testcase:
Packit 62fe53
#
Packit 62fe53
# /* { dg-prms-id 1234 } */
Packit 62fe53
# int foo { return 0; } /* { dg-build fatal "some comment" } */
Packit 62fe53
#
Packit 62fe53
# we return:
Packit 62fe53
#
Packit 62fe53
# { dg-prms-id 1 1234 } { dg-build 2 fatal "some comment" }
Packit 62fe53
Packit 62fe53
proc dg-get-options { prog } {
Packit 62fe53
    set result ""
Packit 62fe53
Packit 62fe53
    set tmp [grep $prog "{\[ \t\]\+dg-\[-a-z\]\+\[ \t\]\+.*\[ \t\]\+}" line]
Packit 62fe53
    if {![string match "" $tmp]} {
Packit 62fe53
	foreach i $tmp {
Packit 62fe53
	    regexp "(\[0-9\]+)\[ \t\]+{\[ \t\]+(dg-\[-a-z\]+)\[ \t\]+(.*)\[ \t\]+}\[^\}\]*(\n|$)" $i i line cmd args
Packit 62fe53
	    append result " { $cmd $line $args }"
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
    return $result
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
#
Packit 62fe53
# Process optional xfail/target arguments
Packit 62fe53
#
Packit 62fe53
# SELECTOR is "xfail target-triplet-1 ..." or "target target-triplet-1 ..."
Packit 62fe53
# `target-triplet' may be "native".
Packit 62fe53
# For xfail, the result is "F" (expected to Fail) if the current target is
Packit 62fe53
# affected, otherwise "P" (expected to Pass).
Packit 62fe53
# For target, the result is "S" (target is Selected) if the target is selected,
Packit 62fe53
# otherwise "N" (target is Not selected).
Packit 62fe53
#
Packit 62fe53
proc dg-process-target { selector } {
Packit 62fe53
    global target_triplet
Packit 62fe53
Packit 62fe53
    set isnative [isnative]
Packit 62fe53
    set triplet_match 0
Packit 62fe53
Packit 62fe53
    set selector [string trim $selector]
Packit 62fe53
    if {[regexp "^xfail " $selector]} {
Packit 62fe53
	set what xfail
Packit 62fe53
    } elseif {[regexp "^target " $selector]} {
Packit 62fe53
	set what target
Packit 62fe53
    } else {
Packit 62fe53
	# The use of error here and in other dg-xxx utilities is intentional.
Packit 62fe53
	# dg-test will catch them and do the right thing.
Packit 62fe53
	error "syntax error in target selector \"$selector\""
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if {[regexp "^${what}( \[^ \]+-\[^ \]+-\[^ \]+| native)+$" $selector]} {
Packit 62fe53
	regsub "^${what} " $selector "" selector
Packit 62fe53
	foreach triplet $selector {
Packit 62fe53
	    if {[string match $triplet $target_triplet]} {
Packit 62fe53
		set triplet_match 1
Packit 62fe53
	    } elseif { $isnative && $triplet == "native" } {
Packit 62fe53
		set triplet_match 1
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    } else {
Packit 62fe53
	error "syntax error in target selector \"$selector\""
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { $triplet_match } {
Packit 62fe53
	return [expr { $what == "xfail" ? "F" : "S" }]
Packit 62fe53
    } else {
Packit 62fe53
	return [expr { $what == "xfail" ? "P" : "N" }]
Packit 62fe53
    }
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
# Predefined user option handlers.
Packit 62fe53
# The line number is always the first element.
Packit 62fe53
# Note that each of these are varargs procs (they have an `args' argument).
Packit 62fe53
# Tests for optional arguments are coded with ">=" to simplify adding new ones.
Packit 62fe53
#
Packit 62fe53
proc dg-prms-id { args } {
Packit 62fe53
    global prms_id
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 2 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    set prms_id [lindex $args 1]
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
# Set tool options
Packit 62fe53
#
Packit 62fe53
# Different options can be used for different targets by having multiple
Packit 62fe53
# instances, selecting a different target each time.  Since options are
Packit 62fe53
# processed in order, put the default value first.  Subsequent occurrences
Packit 62fe53
# will override previous ones.
Packit 62fe53
#
Packit 62fe53
proc dg-options { args } {
Packit 62fe53
    upvar dg-extra-tool-flags extra-tool-flags
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 3 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { [llength $args] >= 3 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 2]] {
Packit 62fe53
	    "S" { set extra-tool-flags [lindex $args 1] }
Packit 62fe53
	    "N" { }
Packit 62fe53
	    "F" { error "[lindex $args 0]: `xfail' not allowed here" }
Packit 62fe53
	    "P" { error "[lindex $args 0]: `xfail' not allowed here" }
Packit 62fe53
	}
Packit 62fe53
    } else {
Packit 62fe53
	set extra-tool-flags [lindex $args 1]
Packit 62fe53
    }
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
# Record what to do (compile/run/etc.)
Packit 62fe53
#
Packit 62fe53
# Multiple instances are supported (since we don't support target and xfail
Packit 62fe53
# selectors on one line), though it doesn't make much sense to change the
Packit 62fe53
# compile/assemble/link/run field.  Nor does it make any sense to have
Packit 62fe53
# multiple lines of target selectors (use one line).
Packit 62fe53
#
Packit 62fe53
proc dg-do { args } {
Packit 62fe53
    upvar dg-do-what do-what
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 3 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    set doaction [lindex $args 1]
Packit 62fe53
    set selected [lindex ${do-what} 1]	;# selected? (""/S/N)
Packit 62fe53
    set expected [lindex ${do-what} 2]	;# expected to pass/fail (P/F)
Packit 62fe53
Packit 62fe53
    if { [llength $args] >= 3 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 2]] {
Packit 62fe53
	    "S" {
Packit 62fe53
		set selected "S"
Packit 62fe53
	    }
Packit 62fe53
	    "N" {
Packit 62fe53
		# Don't deselect a target if it's been explicitly selected,
Packit 62fe53
		# but indicate a specific target has been selected (so don't
Packit 62fe53
		# do this testcase if it's not appropriate for this target).
Packit 62fe53
		# The user really shouldn't have multiple lines of target
Packit 62fe53
		# selectors, but try to do the intuitive thing (multiple lines
Packit 62fe53
		# are OR'd together).
Packit 62fe53
		if { $selected != "S" } {
Packit 62fe53
		    set selected "N"
Packit 62fe53
		} else {
Packit 62fe53
		    set doaction [lindex ${do-what} 0]
Packit 62fe53
		}
Packit 62fe53
	    }
Packit 62fe53
	    "F" { set expected "F" }
Packit 62fe53
	    "P" {
Packit 62fe53
		# There's nothing to do for "P".  We don't want to clobber a
Packit 62fe53
		# previous xfail for this target.
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    } else {
Packit 62fe53
	# Note: A previous occurrence of `dg-do' with target/xfail selectors
Packit 62fe53
	# is a user mistake.  We clobber previous values here.
Packit 62fe53
	set selected S
Packit 62fe53
	set expected P
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    switch -- [lindex $args 1] {
Packit 62fe53
	"preprocess" { }
Packit 62fe53
	"compile" { }
Packit 62fe53
	"assemble" { }
Packit 62fe53
	"link" { }
Packit 62fe53
	"run" { }
Packit 62fe53
	default {
Packit 62fe53
	    error "[lindex $args 0]: syntax error"
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
    set do-what [list $doaction $selected $expected]
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
proc dg-error { args } {
Packit 62fe53
    upvar dg-messages messages
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 5 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    set xfail ""
Packit 62fe53
    if { [llength $args] >= 4 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 3]] {
Packit 62fe53
	    "F" { set xfail "X" }
Packit 62fe53
	    "P" { set xfail "" }
Packit 62fe53
	    "N" {
Packit 62fe53
		# If we get "N", this error doesn't apply to us so ignore it.
Packit 62fe53
		return
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { [llength $args] >= 5 } {
Packit 62fe53
	switch -- [lindex $args 4] {
Packit 62fe53
	    "." { set line [dg-format-linenum [lindex $args 0]] }
Packit 62fe53
	    "0" { set line "" }
Packit 62fe53
	    "default" { set line [dg-format-linenum [lindex $args 4]] }
Packit 62fe53
	}
Packit 62fe53
    } else {
Packit 62fe53
	set line [dg-format-linenum [lindex $args 0]]
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    lappend messages [list $line "${xfail}ERROR" [lindex $args 1] [lindex $args 2]]
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
proc dg-warning { args } {
Packit 62fe53
    upvar dg-messages messages
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 5 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    set xfail ""
Packit 62fe53
    if { [llength $args] >= 4 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 3]] {
Packit 62fe53
	    "F" { set xfail "X" }
Packit 62fe53
	    "P" { set xfail "" }
Packit 62fe53
	    "N" {
Packit 62fe53
		# If we get "N", this warning doesn't apply to us so ignore it.
Packit 62fe53
		return
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { [llength $args] >= 5 } {
Packit 62fe53
	switch -- [lindex $args 4] {
Packit 62fe53
	    "." { set line [dg-format-linenum [lindex $args 0]] }
Packit 62fe53
	    "0" { set line "" }
Packit 62fe53
	    "default" { set line [dg-format-linenum [lindex $args 4]] }
Packit 62fe53
	}
Packit 62fe53
    } else {
Packit 62fe53
	set line [dg-format-linenum [lindex $args 0]]
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    lappend messages [list $line "${xfail}WARNING" [lindex $args 1] [lindex $args 2]]
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
proc dg-bogus { args } {
Packit 62fe53
    upvar dg-messages messages
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 5 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    set xfail ""
Packit 62fe53
    if { [llength $args] >= 4 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 3]] {
Packit 62fe53
	    "F" { set xfail "X" }
Packit 62fe53
	    "P" { set xfail "" }
Packit 62fe53
	    "N" {
Packit 62fe53
		# If we get "N", this message doesn't apply to us so ignore it.
Packit 62fe53
		return
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { [llength $args] >= 5 } {
Packit 62fe53
	switch -- [lindex $args 4] {
Packit 62fe53
	    "." { set line [dg-format-linenum [lindex $args 0]] }
Packit 62fe53
	    "0" { set line "" }
Packit 62fe53
	    "default" { set line [dg-format-linenum [lindex $args 4]] }
Packit 62fe53
	}
Packit 62fe53
    } else {
Packit 62fe53
	set line [dg-format-linenum [lindex $args 0]]
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    lappend messages [list $line "${xfail}BOGUS" [lindex $args 1] [lindex $args 2]]
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
proc dg-build { args } {
Packit 62fe53
    upvar dg-messages messages
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 4 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    set xfail ""
Packit 62fe53
    if { [ llength $args] >= 4 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 3]] {
Packit 62fe53
	    "F" { set xfail "X" }
Packit 62fe53
	    "P" { set xfail "" }
Packit 62fe53
	    "N" {
Packit 62fe53
		# If we get "N", this lossage doesn't apply to us so ignore it.
Packit 62fe53
		return
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    lappend messages [list [lindex $args 0] "${xfail}BUILD" [lindex $args 1] [lindex $args 2]]
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
proc dg-excess-errors { args } {
Packit 62fe53
    upvar dg-excess-errors-flag excess-errors-flag
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 3 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { [llength $args] >= 3 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 2]] {
Packit 62fe53
	    "F" { set excess-errors-flag 1 }
Packit 62fe53
	    "S" { set excess-errors-flag 1 }
Packit 62fe53
	}
Packit 62fe53
    } else {
Packit 62fe53
	set excess-errors-flag 1
Packit 62fe53
    }
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
# Indicate expected program output.
Packit 62fe53
#
Packit 62fe53
# We support multiple occurrences, but we do not implicitly insert newlines
Packit 62fe53
# between them.
Packit 62fe53
#
Packit 62fe53
# Note that target boards don't all support this kind of thing so it's a good
Packit 62fe53
# idea to specify the target all the time.  If one or more targets are
Packit 62fe53
# explicitly selected, the test won't be performed if we're not one of them
Packit 62fe53
# (as long as we were never mentioned).
Packit 62fe53
#
Packit 62fe53
# If you have target dependent output and want to set an xfail for one or more
Packit 62fe53
# of them, use { dg-output "" { xfail a-b-c ... } }.  The "" won't contribute
Packit 62fe53
# to the expected output.
Packit 62fe53
#
Packit 62fe53
proc dg-output { args } {
Packit 62fe53
    upvar dg-output-text output-text
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 3 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Allow target dependent output.
Packit 62fe53
Packit 62fe53
    set expected [lindex ${output-text} 0]
Packit 62fe53
    if { [llength $args] >= 3 } {
Packit 62fe53
	switch -- [dg-process-target [lindex $args 2]] {
Packit 62fe53
	    "N" { return }
Packit 62fe53
	    "S" { }
Packit 62fe53
	    "F" { set expected "F" }
Packit 62fe53
	    # Don't override a previous xfail.
Packit 62fe53
	    "P" { }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { [llength ${output-text}] == 1 } {
Packit 62fe53
	# First occurrence.
Packit 62fe53
	set output-text [list $expected [lindex $args 1]]
Packit 62fe53
    } else {
Packit 62fe53
	set output-text [list $expected "[lindex ${output-text} 1][lindex $args 1]"]
Packit 62fe53
    }
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
proc dg-final { args } {
Packit 62fe53
    upvar dg-final-code final-code
Packit 62fe53
Packit 62fe53
    if { [llength $args] > 2 } {
Packit 62fe53
	error "[lindex $args 0]: too many arguments"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    append final-code "[lindex $args 1]\n"
Packit 62fe53
}
Packit 62fe53

Packit 62fe53
# Set up our environment
Packit 62fe53
#
Packit 62fe53
# There currently isn't much to do, but always calling it allows us to add
Packit 62fe53
# enhancements without having to update our callers.
Packit 62fe53
# It must be run before calling `dg-test'.
Packit 62fe53
#
Packit 62fe53
proc dg-init { } {
Packit 62fe53
}
Packit 62fe53

Packit 62fe53
# dg-runtest -- simple main loop useful to most testsuites
Packit 62fe53
#
Packit 62fe53
# OPTIONS is a set of options to always pass.
Packit 62fe53
# DEFAULT_EXTRA_OPTIONS is a set of options to pass if the testcase
Packit 62fe53
# doesn't specify any (with dg-option).
Packit 62fe53
Packit 62fe53
proc dg-runtest { testcases options default-extra-options } {
Packit 62fe53
    global runtests
Packit 62fe53
Packit 62fe53
    foreach testcase $testcases {
Packit 62fe53
	# If we're only testing specific files and this isn't one of them, skip it.
Packit 62fe53
	if {![runtest_file_p $runtests $testcase]} {
Packit 62fe53
	    continue
Packit 62fe53
	}
Packit 62fe53
	verbose "Testing [file tail [file dirname $testcase]]/[file tail $testcase]"
Packit 62fe53
	dg-test $testcase $options ${default-extra-options}
Packit 62fe53
    }
Packit 62fe53
}
Packit 62fe53

Packit 62fe53
# dg-trim-dirname -- rip DIR_NAME out of FILE_NAME
Packit 62fe53
#
Packit 62fe53
# Syntax: dg-trim-dirname dir_name file_name
Packit 62fe53
# We need to go through this contortion in order to properly support
Packit 62fe53
# directory-names which might have embedded regexp special characters.
Packit 62fe53
#
Packit 62fe53
proc dg-trim-dirname { dir_name file_name } {
Packit 62fe53
    set special_character "\[\?\+\-\.\(\)\$\|\]"
Packit 62fe53
    regsub -all -- $special_character $dir_name "\\\\&" dir_name
Packit 62fe53
    regsub "^$dir_name/?" $file_name "" file_name
Packit 62fe53
    return $file_name
Packit 62fe53
}
Packit 62fe53
Packit 62fe53
# dg-test -- runs a new style DejaGnu test
Packit 62fe53
#
Packit 62fe53
# Syntax: dg-test [-keep-output] prog tool_flags default_extra_tool_flags
Packit 62fe53
#
Packit 62fe53
# PROG is the full path name of the file to pass to the tool (eg: compiler).
Packit 62fe53
# TOOL_FLAGS is a set of options to always pass.
Packit 62fe53
# DEFAULT_EXTRA_TOOL_FLAGS are additional options if the testcase has none.
Packit 62fe53
Packit 62fe53
#proc dg-test { prog tool_flags default_extra_tool_flags } {
Packit 62fe53
proc dg-test { args } {
Packit 62fe53
    global dg-do-what-default dg-interpreter-batch-mode dg-linenum-format
Packit 62fe53
    global errorCode errorInfo
Packit 62fe53
    global tool
Packit 62fe53
    global srcdir
Packit 62fe53
    global host_triplet target_triplet
Packit 62fe53
Packit 62fe53
    set keep 0
Packit 62fe53
    set i 0
Packit 62fe53
Packit 62fe53
    if { [string index [lindex $args 0] 0] == "-" } {
Packit 62fe53
	for { set i 0 } { $i < [llength $args] } { incr i } {
Packit 62fe53
	    if { [lindex $args $i] == "--" } {
Packit 62fe53
		incr i
Packit 62fe53
		break
Packit 62fe53
	    } elseif { [lindex $args $i] == "-keep-output" } {
Packit 62fe53
		set keep 1
Packit 62fe53
	    } elseif { [string index [lindex $args $i] 0] == "-" } {
Packit 62fe53
		clone_output "ERROR: dg-test: illegal argument: [lindex $args $i]"
Packit 62fe53
		return
Packit 62fe53
	    } else {
Packit 62fe53
		break
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    if { $i + 3 != [llength $args] } {
Packit 62fe53
	clone_output "ERROR: dg-test: missing arguments in call"
Packit 62fe53
	return
Packit 62fe53
    }
Packit 62fe53
    set prog [lindex $args $i]
Packit 62fe53
    set tool_flags [lindex $args [expr {$i + 1}]]
Packit 62fe53
    set default_extra_tool_flags [lindex $args [expr {$i + 2}]]
Packit 62fe53
Packit 62fe53
    set text "\[- A-Za-z0-9\.\;\"\_\:\'\`\(\)\!\#\=\+\?\&\*]*"
Packit 62fe53
Packit 62fe53
    set name [dg-trim-dirname $srcdir $prog]
Packit 62fe53
    # If we couldn't rip $srcdir out of `prog' then just do the best we can.
Packit 62fe53
    # The point is to reduce the unnecessary noise in the logs.  Don't strip
Packit 62fe53
    # out too much because different testcases with the same name can confuse
Packit 62fe53
    # `test-tool'.
Packit 62fe53
    if {[string match "/*" $name]} {
Packit 62fe53
	set name "[file tail [file dirname $prog]]/[file tail $prog]"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # We append the compilation flags, if any, to ensure that the test case
Packit 62fe53
    # names are unique.
Packit 62fe53
    if { "$tool_flags" != "" } {
Packit 62fe53
	set name "$name $tool_flags"
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Process any embedded dg options in the testcase.
Packit 62fe53
Packit 62fe53
    # Use "" for the second element of dg-do-what so we can tell if it's been
Packit 62fe53
    # explicitly set to "S".
Packit 62fe53
    set dg-do-what [list ${dg-do-what-default} "" P]
Packit 62fe53
    set dg-excess-errors-flag 0
Packit 62fe53
    set dg-messages ""
Packit 62fe53
    set dg-extra-tool-flags $default_extra_tool_flags
Packit 62fe53
    set dg-final-code ""
Packit 62fe53
Packit 62fe53
    # `dg-output-text' is a list of two elements: pass/fail and text.
Packit 62fe53
    # Leave second element off for now (indicates "don't perform test")
Packit 62fe53
    set dg-output-text "P"
Packit 62fe53
Packit 62fe53
    # Define our own "special function" `unknown' so we catch spelling errors.
Packit 62fe53
    # But first rename the existing one so we can restore it afterwards.
Packit 62fe53
    if { [info procs dg-save-unknown] == [list] } {
Packit 62fe53
	rename unknown dg-save-unknown
Packit 62fe53
	proc unknown { args } {
Packit 62fe53
	    return -code error "unknown dg option: $args"
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    set tmp [dg-get-options $prog]
Packit 62fe53
    foreach op $tmp {
Packit 62fe53
	verbose "Processing option: $op" 3
Packit 62fe53
	set status [catch "$op" errmsg]
Packit 62fe53
	if { $status != 0 } {
Packit 62fe53
	    if { 0 && [info exists errorInfo] } {
Packit 62fe53
		# This also prints a backtrace which will just confuse
Packit 62fe53
		# testcase writers, so it's disabled.
Packit 62fe53
		perror "$name: $errorInfo\n"
Packit 62fe53
	    } else {
Packit 62fe53
		perror "$name: $errmsg for \"$op\"\n"
Packit 62fe53
	    }
Packit 62fe53
	    perror "$name: $errmsg for \"$op\"" 0
Packit 62fe53
	    return
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Restore normal error handling.
Packit 62fe53
    if { [info procs dg-save-unknown] != [list] } {
Packit 62fe53
	rename unknown ""
Packit 62fe53
	rename dg-save-unknown unknown
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # If we're not supposed to try this test on this target, we're done.
Packit 62fe53
    if { [lindex ${dg-do-what} 1] == "N" } {
Packit 62fe53
	unsupported "$name"
Packit 62fe53
	verbose "$name not supported on this target, skipping it" 3
Packit 62fe53
	return
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Run the tool and analyze the results.
Packit 62fe53
    # The result of ${tool}-dg-test is in a bit of flux.
Packit 62fe53
    # Currently it is the name of the output file (or "" if none).
Packit 62fe53
    # If we need more than this it will grow into a list of things.
Packit 62fe53
    # No intention is made (at this point) to preserve upward compatibility
Packit 62fe53
    # (though at some point we'll have to).
Packit 62fe53
Packit 62fe53
    set results [${tool}-dg-test $prog [lindex ${dg-do-what} 0] "$tool_flags ${dg-extra-tool-flags}"]
Packit 62fe53
Packit 62fe53
    set comp_output [lindex $results 0]
Packit 62fe53
    set output_file [lindex $results 1]
Packit 62fe53
Packit 62fe53
    foreach i ${dg-messages} {
Packit 62fe53
	verbose "Scanning for message: $i" 4
Packit 62fe53
Packit 62fe53
	# Remove all error messages for the line [lindex $i 0]
Packit 62fe53
	# in the source file.  If we find any, success!
Packit 62fe53
	set line [lindex $i 0]
Packit 62fe53
	set pattern [lindex $i 2]
Packit 62fe53
	set comment [lindex $i 3]
Packit 62fe53
	if {[regsub -all "(^|\n)(\[^\n\]+$line\[^\n\]*($pattern)\[^\n\]*\n?)+" $comp_output "\n" comp_output]} {
Packit 62fe53
	    set comp_output [string trimleft $comp_output]
Packit 62fe53
	    set ok pass
Packit 62fe53
	    set uhoh fail
Packit 62fe53
	} else {
Packit 62fe53
	    set ok fail
Packit 62fe53
	    set uhoh pass
Packit 62fe53
	}
Packit 62fe53
Packit 62fe53
	# $line will either be a formatted line number or a number all by
Packit 62fe53
	# itself.  Delete the formatting.
Packit 62fe53
	scan $line ${dg-linenum-format} line
Packit 62fe53
	switch -- [lindex $i 1] {
Packit 62fe53
	    "ERROR" {
Packit 62fe53
		$ok "$name $comment (test for errors, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "XERROR" {
Packit 62fe53
		x$ok "$name $comment (test for errors, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "WARNING" {
Packit 62fe53
		$ok "$name $comment (test for warnings, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "XWARNING" {
Packit 62fe53
		x$ok "$name $comment (test for warnings, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "BOGUS" {
Packit 62fe53
		$uhoh "$name $comment (test for bogus messages, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "XBOGUS" {
Packit 62fe53
		x$uhoh "$name $comment (test for bogus messages, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "BUILD" {
Packit 62fe53
		$uhoh "$name $comment (test for build failure, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "XBUILD" {
Packit 62fe53
		x$uhoh "$name $comment (test for build failure, line $line)"
Packit 62fe53
	    }
Packit 62fe53
	    "EXEC" { }
Packit 62fe53
	    "XEXEC" { }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Remove messages from the tool that we can ignore.
Packit 62fe53
    set comp_output [prune_warnings $comp_output]
Packit 62fe53
Packit 62fe53
    if { [info procs ${tool}-dg-prune] != "" } {
Packit 62fe53
	set comp_output [${tool}-dg-prune $target_triplet $comp_output]
Packit 62fe53
	switch -glob -- $comp_output {
Packit 62fe53
	    "::untested::*" {
Packit 62fe53
		regsub "::untested::" $comp_output "" message
Packit 62fe53
		untested "$name: $message"
Packit 62fe53
		return
Packit 62fe53
	    }
Packit 62fe53
	    "::unresolved::*" {
Packit 62fe53
		regsub "::unresolved::" $comp_output "" message
Packit 62fe53
		unresolved "$name: $message"
Packit 62fe53
		return
Packit 62fe53
	    }
Packit 62fe53
	    "::unsupported::*" {
Packit 62fe53
		regsub "::unsupported::" $comp_output "" message
Packit 62fe53
		unsupported "$name: $message"
Packit 62fe53
		return
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # See if someone forgot to delete the extra lines.
Packit 62fe53
    regsub -all "\n+" $comp_output "\n" comp_output
Packit 62fe53
    regsub "^\n+" $comp_output "" comp_output
Packit 62fe53
Packit 62fe53
    # Don't do this if we're testing an interpreter.
Packit 62fe53
    # FIXME: why?
Packit 62fe53
    if { ${dg-interpreter-batch-mode} == 0 } {
Packit 62fe53
	# Catch excess errors (new bugs or incomplete testcases).
Packit 62fe53
	if {${dg-excess-errors-flag}} {
Packit 62fe53
	    setup_xfail "*-*-*"
Packit 62fe53
	}
Packit 62fe53
	if {![string match "" $comp_output]} {
Packit 62fe53
	    fail "$name (test for excess errors)"
Packit 62fe53
	    send_log "Excess errors:\n$comp_output\n"
Packit 62fe53
	} else {
Packit 62fe53
	    pass "$name (test for excess errors)"
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Run the executable image if asked to do so.
Packit 62fe53
    # FIXME: This is the only place where we assume a standard meaning to
Packit 62fe53
    # the `keyword' argument of dg-do.  This could be cleaned up.
Packit 62fe53
    if { [lindex ${dg-do-what} 0] == "run" } {
Packit 62fe53
	if {![file exists $output_file]} {
Packit 62fe53
	    unresolved "$name compilation failed to produce executable"
Packit 62fe53
	} else {
Packit 62fe53
	    set status -1
Packit 62fe53
	    set result [${tool}_load $output_file]
Packit 62fe53
	    set status [lindex $result 0]
Packit 62fe53
	    set output [lindex $result 1]
Packit 62fe53
	    if { [lindex ${dg-do-what} 2] == "F" } {
Packit 62fe53
		setup_xfail "*-*-*"
Packit 62fe53
	    }
Packit 62fe53
	    if { "$status" == "pass" } {
Packit 62fe53
		pass "$name execution test"
Packit 62fe53
		verbose "Exec succeeded." 3
Packit 62fe53
		if { [llength ${dg-output-text}] > 1 } {
Packit 62fe53
		    if { [lindex ${dg-output-text} 0] == "F" } {
Packit 62fe53
			setup_xfail "*-*-*"
Packit 62fe53
		    }
Packit 62fe53
		    set texttmp [lindex ${dg-output-text} 1]
Packit 62fe53
		    if { ![regexp -- $texttmp ${output}] } {
Packit 62fe53
			fail "$name output pattern test"
Packit 62fe53
			send_log "Output was:\n${output}\nShould match:\n$texttmp\n"
Packit 62fe53
			verbose "Failed test for output pattern $texttmp" 3
Packit 62fe53
		    } else {
Packit 62fe53
			pass "$name output pattern test"
Packit 62fe53
			verbose "Passed test for output pattern $texttmp" 3
Packit 62fe53
		    }
Packit 62fe53
		    unset texttmp
Packit 62fe53
		}
Packit 62fe53
	    } elseif { "$status" == "fail" } {
Packit 62fe53
		# It would be nice to get some info out of errorCode.
Packit 62fe53
		if {[info exists errorCode]} {
Packit 62fe53
		    verbose "Exec failed, errorCode: $errorCode" 3
Packit 62fe53
		} else {
Packit 62fe53
		    verbose "Exec failed, errorCode not defined!" 3
Packit 62fe53
		}
Packit 62fe53
		fail "$name execution test"
Packit 62fe53
	    } else {
Packit 62fe53
		$status "$name execution test"
Packit 62fe53
	    }
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Are there any further tests to perform?
Packit 62fe53
    # Note that if the program has special run-time requirements, running
Packit 62fe53
    # of the program can be delayed until here.  Ditto for other situations.
Packit 62fe53
    # It would be a bit cumbersome though.
Packit 62fe53
Packit 62fe53
    if {![string match ${dg-final-code} ""]} {
Packit 62fe53
	regsub -all "\\\\(\[{}\])" ${dg-final-code} "\\1" dg-final-code
Packit 62fe53
	# Note that the use of `args' here makes this a varargs proc.
Packit 62fe53
	proc dg-final-proc { args } ${dg-final-code}
Packit 62fe53
	verbose "Running dg-final tests." 3
Packit 62fe53
	verbose "dg-final-proc:\n[info body dg-final-proc]" 4
Packit 62fe53
	if {[catch "dg-final-proc $prog" errmsg]} {
Packit 62fe53
	    perror "$name: error executing dg-final: $errmsg" 0
Packit 62fe53
	}
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # Do some final clean up.
Packit 62fe53
    # When testing an interpreter, we don't compile something and leave an
Packit 62fe53
    # output file.
Packit 62fe53
    if { ! ${keep} && ${dg-interpreter-batch-mode} == 0 } {
Packit 62fe53
	catch "file delete -force -- $output_file"
Packit 62fe53
    }
Packit 62fe53
}
Packit 62fe53

Packit 62fe53
# Do any necessary cleanups.
Packit 62fe53
# This is called at the end to undo anything dg-init did (that needs undoing).
Packit 62fe53
#
Packit 62fe53
proc dg-finish { } {
Packit 62fe53
    # Reset this in case caller wonders whether s/he should.
Packit 62fe53
    global prms_id
Packit 62fe53
    set prms_id 0
Packit 62fe53
Packit 62fe53
    # The framework doesn't like to see any error remnants, so remove them.
Packit 62fe53
    global errorInfo
Packit 62fe53
    if {[info exists errorInfo]} {
Packit 62fe53
	unset errorInfo
Packit 62fe53
    }
Packit 62fe53
Packit 62fe53
    # If the tool has a "finish" routine, call it.
Packit 62fe53
    # There may be a bit of duplication (eg: resetting prms_id), leave it.
Packit 62fe53
    # Let's keep these procs robust.
Packit 62fe53
    global tool
Packit 62fe53
    if {![string match "" [info procs ${tool}_finish]]} {
Packit 62fe53
	${tool}_finish
Packit 62fe53
    }
Packit 62fe53
}