+2017-06-04 Dominique d'Humieres <dominiq@lps.ens.fr>
+
+ * lib/fortran-modules.exp (igrep): New procedure, case insensitive
+ vesrion of the dejagnu grep.
+ (list-module-names): Use it and adjust the regular expressions for
+ modules and submodules.
+ * gfortran.dg/prof/prof.exp: Cleanup modules.
+ * gfortran.dg/allocate_class_4.f90: Remove cleanup-(sub)?modules
+ directives.
+ * gfortran.dg/altreturn_8.f90: Likewise.
+ * gfortran.dg/associate_12.f90: Likewise.
+ * gfortran.dg/c_f_pointer_shape_test.f90: Likewise.
+ * gfortran.dg/charlen_15.f90: Likewise.
+ * gfortran.dg/class_4a.f03: Likewise.
+ * gfortran.dg/class_54.f90: Likewise.
+ * gfortran.dg/class_dummy_4.f03: Likewise.
+ * gfortran.dg/class_dummy_5.f90: Likewise.
+ * gfortran.dg/constructor_9.f90: Likewise.
+ * gfortran.dg/dec_structure_15.f90: Likewise.
+ * gfortran.dg/do_check_8.f90: Likewise.
+ * gfortran.dg/dtio_26.f03: Likewise.
+ * gfortran.dg/dynamic_dispatch_12.f90: Likewise.
+ * gfortran.dg/equiv_9.f90: Likewise.
+ * gfortran.dg/extends_15.f90: Likewise.
+ * gfortran.dg/finalize_22.f90: Likewise.
+ * gfortran.dg/finalize_23.f90: Likewise.
+ * gfortran.dg/generic_26.f90: Likewise.
+ * gfortran.dg/generic_27.f90: Likewise.
+ * gfortran.dg/namelist_76.f90: Likewise.
+ * gfortran.dg/pointer_init_8.f90: Likewise.
+ * gfortran.dg/pr61318.f90: Likewise.
+ * gfortran.dg/pr77260_1.f90: Likewise.
+ * gfortran.dg/pr77260_2.f90: Likewise.
+ * gfortran.dg/pr77420_3.f90: Likewise.
+ * gfortran.dg/proc_ptr_39.f90: Likewise.
+ * gfortran.dg/proc_ptr_41.f90: Likewise.
+ * gfortran.dg/proc_ptr_42.f90: Likewise.
+ * gfortran.dg/proc_ptr_comp_43.f90: Likewise.
+ * gfortran.dg/submodule_1.f08: Likewise.
+ * gfortran.dg/submodule_10.f08: Likewise.
+ * gfortran.dg/submodule_14.f08: Likewise.
+ * gfortran.dg/submodule_15.f08: Likewise.
+ * gfortran.dg/submodule_2.f08: Likewise.
+ * gfortran.dg/submodule_5.f08: Likewise.
+ * gfortran.dg/submodule_6.f08: Likewise.
+ * gfortran.dg/submodule_7.f08: Likewise.
+ * gfortran.dg/submodule_8.f08: Likewise.
+ * gfortran.dg/submodule_9.f08: Likewise.
+ * gfortran.dg/transfer_class_2.f90: Likewise.
+ * gfortran.dg/typebound_assignment_7.f90: Likewise.
+ * gfortran.dg/typebound_call_24.f03: Likewise.
+ * gfortran.dg/typebound_call_25.f90: Likewise.
+ * gfortran.dg/typebound_deferred_1.f90: Likewise.
+ * gfortran.dg/typebound_generic_12.f03: Likewise.
+ * gfortran.dg/typebound_generic_13.f03: Likewise.
+ * gfortran.dg/typebound_generic_14.f03: Likewise.
+ * gfortran.dg/typebound_generic_15.f90: Likewise.
+ * gfortran.dg/typebound_operator_16.f03: Likewise.
+ * gfortran.dg/typebound_operator_18.f90: Likewise.
+ * gfortran.dg/typebound_operator_20.f90: Likewise.
+ * gfortran.dg/typebound_override_3.f90: Likewise.
+ * gfortran.dg/typebound_override_4.f90: Likewise.
+ * gfortran.dg/typebound_override_5.f90: Likewise.
+ * gfortran.dg/typebound_override_6.f90: Likewise.
+ * gfortran.dg/typebound_override_7.f90: Likewise.
+ * gfortran.dg/typebound_proc_28.f03: Likewise.
+ * gfortran.dg/typebound_proc_29.f90: Likewise.
+ * gfortran.dg/typebound_proc_30.f90: Likewise.
+ * gfortran.dg/typebound_proc_31.f90: Likewise.
+ * gfortran.dg/typebound_proc_32.f90: Likewise.
+ * gfortran.dg/typebound_proc_33.f90: Likewise.
+ * gfortran.dg/unlimited_polymorphic_16.f90: Likewise.
+ * gfortran.dg/unlimited_polymorphic_19.f90: Likewise.
+ * gfortran.dg/unlimited_polymorphic_24.f03: Likewise.
+ * gfortran.dg/use_only_3.f90: Likewise.
+ * gfortran.dg/use_without_only_1.f90: Likewise.
+ * gfortran.dg/warn_unused_function.f90: Likewise.
+ * gfortran.dg/warn_unused_function_2.f90: Likewise.
+ * gfortran.dg/ieee/ieee_8.f90: Likewise.
2017-06-04 Marek Polacek <polacek@redhat.com>
PR c/80919
end subroutine
end module integrable_model_module
-
-! { dg-final { cleanup-modules "integrable_model_module" } }
-
-! { dg-do compile }\r
-! { dg-options "-std=gnu" }\r
-!\r
-! PR 56284: [OOP] ICE with alternate return in type-bound procedure\r
-!\r
-! Contributed by Arjen Markus <arjen.markus@deltares.nl>\r
-\r
-module try_this\r
- implicit none\r
-\r
- type :: table_t\r
- contains\r
- procedure, nopass :: getRecord\r
- end type\r
-\r
-contains\r
-\r
- subroutine getRecord ( * )\r
- end subroutine\r
-\r
-end module\r
-\r
-! { dg-final { cleanup-modules "try_this" } }\r
+! { dg-do compile }
+! { dg-options "-std=gnu" }
+!
+! PR 56284: [OOP] ICE with alternate return in type-bound procedure
+!
+! Contributed by Arjen Markus <arjen.markus@deltares.nl>
+
+module try_this
+ implicit none
+
+ type :: table_t
+ contains
+ procedure, nopass :: getRecord
+ end type
+
+contains
+
+ subroutine getRecord ( * )
+ end subroutine
+
+end module
print *, 1. + b
end associate
end program
-
-! { dg-final { cleanup-modules "assoc_err_m" } }
call c_f_pointer(cPtr, myArrayPtr) ! { dg-error "Expected SHAPE argument to C_F_POINTER with array FPTR" }
end subroutine test_0
end module c_f_pointer_shape_test
-
-! { dg-final { cleanup-modules "c_f_pointer_shape_test" } }
use m
if (trim(x%c(1)) /= 'ab') call abort
end program foo
-! { dg-final { cleanup-modules "m" } }
-
type t
end type t
end module m
-! { dg-final { cleanup-modules "m m2" } }
use m
class(t), pointer :: a2
end subroutine
-
-! { dg-final { cleanup-modules "m" } }
type(c_stv), allocatable, intent(out) :: y
end subroutine
end
-
-! { dg-final { cleanup-modules "m1 m2" } }
class(t), intent(out) :: x
end subroutine
end
-
-! { dg-final { cleanup-modules "m" } }
cfd=cfmde() ! { dg-error "Can't convert" }
end subroutine
end module
-
-! { dg-final { cleanup-modules "cf" } }
a2 = 0.0
end function
end module
-! { dg-final { cleanup-modules "dec_structure_15" } }
call sub(undeclared)
end do
end program main
-! { dg-final { cleanup-modules "foo" } }
read( unit=s, fmt=*, iostat=istat, iomsg=imsg) foo
if (imsg.ne."End of record") call abort
end program p
-
-! { dg-final { cleanup-modules "t_m" } }
end subroutine
end
-
-! { dg-final { cleanup-modules "TestResult_mod BaseTestRunner_mod TestRunner_mod" } }
implicit none
if (x2 /= 2) call abort
end subroutine
-! { dg-final { cleanup-modules "constant" } }
type :: t1
end type
end
-
-! { dg-final { cleanup-modules "ct" } }
class(cfml), intent(inout) :: s
end subroutine mld
end module cf
-
-! { dg-final { cleanup-modules "cf" } }
end function
end module
-
-! { dg-final { cleanup-modules "ObjectLists" } }
end function
end
-
-! { dg-final { cleanup-modules "a" } }
if (testIF(cos)/=1.0) call abort()
end program
-
-! { dg-final { cleanup-modules "m" } }
if (len(s8) /= x8) call abort
end subroutine
-
-! { dg-final { cleanup-modules "foo bar" } }
write(10, nml=write_data_list)
close(10)
end subroutine write_data
-
-! { dg-final { cleanup-modules "data" } }
if (.not. associated(py, y)) call abort()
if (.not. same_type_as(py, y)) call abort()
end
-
-! { dg-final { cleanup-modules "m" } }
use gbl_interfaces
call gagout(seve%e,'Some string') ! { dg-error "Type mismatch in argument" }
end program test
-! { dg-final { cleanup-modules "gbl_interfaces gbl_message" } }
implicit none
print *,f2()
end program
-! { dg-final { cleanup-modules "foo" } }
implicit none
print *,f2()
end program
-! { dg-final { cleanup-modules "foo" } }
integer :: h5p_default_f, h5p_flags
equivalence(h5p_flags, h5p_default_f)
end module h5global
-! { dg-final { cleanup-modules "h5global" } }
use Module1
use Module2
end program
-
-! { dg-final { cleanup-modules "Module1 Module2" } }
ptr => generic_name_get_proc_ptr()
end program
-
-! { dg-final { cleanup-modules "test" } }
use m2
call ns_dirdata(f)
end
-
-! { dg-final { cleanup-modules "m1 m2" } }
# ordering using -fprofile-generate followed by -fprofile-use.
load_lib target-supports.exp
+load_lib fortran-modules.exp
# Some targets don't support tree profiling.
if { ![check_profiling_available "-fprofile-generate"] } {
if ![runtest_file_p $runtests $src] then {
continue
}
+ list-module-names $src
profopt-execute $src
+ cleanup-modules ""
}
foreach src [lsort [glob -nocomplain $srcdir/$subdir/*.f*]] {
message2 = ""
end subroutine
end program
-! { dg-final { cleanup-submodules "foo_interface@foo_interface_son" } }
-! { dg-final { cleanup-submodules "foo_interface@foo_interface_grandson" } }
-! { dg-final { cleanup-submodules "foo_interface@foo_interface_daughter" } }
stop
end program testlk
-! { dg-final { cleanup-submodules "error_mod@error_impl_mod" } }
-
x = 10
if (fcn1 (x) .ne. 0) call abort
end
-! { dg-final { cleanup-submodules "test@testson" } }
incr = 1
if (a3(i) .ne. 11) call abort
end
-! { dg-final { cleanup-submodules "a@a_son" } }
if (any (arg%greeting .ne. ["adieu, people!", "adieu, people!"])) call abort
contains
end program
-! { dg-final { cleanup-submodules "foo_interface@foo_interface_son" } }
-! { dg-final { cleanup-submodules "foo_interface@foo_interface_daughter" } }
end SUBMODULE foo_interface_daughter
end
-! { dg-final { cleanup-submodules "foo_interface@foo_interface_daughter" } }
call p_a(a, create_b([3,4,5]))
call print(a)
end program p
-! { dg-final { cleanup-submodules "mod_a@imp_p_a" } }
-! { dg-final { cleanup-submodules "mod_b@imp_create" } }
-
call verify_cleanup (c_1, c_2)
!...
end program main
-! { dg-final { cleanup-submodules "color_points@color_points_a" } }
-! { dg-final { cleanup-submodules "color_points@color_points_b" } }
call abort
end if
end program
-! { dg-final { cleanup-submodules "mod_a@mod_s" } }
implicit none
call p()
end program
-! { dg-final { cleanup-submodules "mod_a@b" } }
if (c%i /= 4) call abort()
end
-
-! { dg-final { cleanup-modules "m" } }
end select
end
-
-! { dg-final { cleanup-modules "mod1 mod2" } }
class(aqq_t) :: aqq ! { dg-error "must be dummy, allocatable or pointer" }
call aqq%aqq_init
end program
-
-! { dg-final { cleanup-modules "aqq_m" } }
END SUBROUTINE
END MODULE
-
-! { dg-final { cleanup-modules "my_mod" } }
end subroutine inter
end module m
-
-! { dg-final { cleanup-modules "m" } }
class(t) :: this
end subroutine sub2
end module m
-
-! { dg-final { cleanup-modules "m" } }
end subroutine
end module
-
-! { dg-final { cleanup-modules "m" } }
end subroutine
end module
-
-! { dg-final { cleanup-modules "a_mod" } }
end Type
end module
-
-! { dg-final { cleanup-modules "Objects" } }
myadd = a%x + b
end function MyAdd
end module
-
-! { dg-final { cleanup-modules "M1 M2" } }
class(athlete) ,intent(in) :: this
end function
end module
-
-! { dg-final { cleanup-modules "athlete_module" } }
if (h1%sum(h2) /= 1) call abort()
end
-
-! { dg-final { cleanup-modules "overwrite" } }
name = "name_B"
end function
end module
-
-! { dg-final { cleanup-modules "dtAs dtBs" } }
class(r_type) :: mapout
end subroutine
end module
-
-! { dg-final { cleanup-modules "base_mod r_mod" } }
-! { dg-do compile }\r
-!\r
-! PR 54190: TYPE(*)/assumed-rank: Type/rank check too relaxed for dummy procedure\r
-! PR 57217: [4.7/4.8/4.9 Regression][OOP] Accepts invalid TBP overriding - lacking arguments check\r
-!\r
-! Contributed by Tobias Burnus <burnus@gcc.gnu.org>\r
-\r
-module base_mod\r
- implicit none\r
- type base_type\r
- integer :: kind\r
- contains\r
- procedure, pass(map) :: clone => base_clone\r
- end type\r
-contains\r
- subroutine base_clone(map,mapout,info)\r
- class(base_type), intent(inout) :: map\r
- class(base_type), intent(inout) :: mapout\r
- integer :: info\r
- end subroutine\r
-end module\r
-\r
-module r_mod\r
- use base_mod\r
- implicit none\r
- type, extends(base_type) :: r_type\r
- real :: dat\r
- contains\r
- procedure, pass(map) :: clone => r_clone ! { dg-error "Type mismatch in argument" }\r
- end type\r
-contains\r
- subroutine r_clone(map,mapout,info)\r
- class(r_type), intent(inout) :: map\r
-!gcc$ attributes no_arg_check :: mapout\r
- integer, intent(inout) :: mapout\r
- integer :: info\r
- end subroutine\r
-end module\r
-\r
-! { dg-final { cleanup-modules "base_mod r_mod" } }\r
+! { dg-do compile }
+!
+! PR 54190: TYPE(*)/assumed-rank: Type/rank check too relaxed for dummy procedure
+! PR 57217: [4.7/4.8/4.9 Regression][OOP] Accepts invalid TBP overriding - lacking arguments check
+!
+! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
+
+module base_mod
+ implicit none
+ type base_type
+ integer :: kind
+ contains
+ procedure, pass(map) :: clone => base_clone
+ end type
+contains
+ subroutine base_clone(map,mapout,info)
+ class(base_type), intent(inout) :: map
+ class(base_type), intent(inout) :: mapout
+ integer :: info
+ end subroutine
+end module
+
+module r_mod
+ use base_mod
+ implicit none
+ type, extends(base_type) :: r_type
+ real :: dat
+ contains
+ procedure, pass(map) :: clone => r_clone ! { dg-error "Type mismatch in argument" }
+ end type
+contains
+ subroutine r_clone(map,mapout,info)
+ class(r_type), intent(inout) :: map
+!gcc$ attributes no_arg_check :: mapout
+ integer, intent(inout) :: mapout
+ integer :: info
+ end subroutine
+end module
-! { dg-do compile }\r
-!\r
-! PR 54190: TYPE(*)/assumed-rank: Type/rank check too relaxed for dummy procedure\r
-! PR 57217: [4.7/4.8/4.9 Regression][OOP] Accepts invalid TBP overriding - lacking arguments check\r
-!\r
-! Contributed by Tobias Burnus <burnus@gcc.gnu.org>\r
-\r
-module base_mod\r
- implicit none\r
- type base_type\r
- integer :: kind\r
- contains\r
- procedure, pass(map) :: clone => base_clone\r
- end type\r
-contains\r
- subroutine base_clone(map,mapout,info)\r
- class(base_type), intent(inout) :: map\r
- class(base_type), intent(inout) :: mapout\r
- integer :: info\r
- end subroutine\r
-end module\r
-\r
-module r_mod\r
- use base_mod\r
- implicit none\r
- type, extends(base_type) :: r_type\r
- real :: dat\r
- contains\r
- procedure, pass(map) :: clone => r_clone ! { dg-error "Rank mismatch in argument" }\r
- end type\r
-contains\r
- subroutine r_clone(map,mapout,info)\r
- class(r_type), intent(inout) :: map\r
- class(base_type), intent(inout) :: mapout(..)\r
- integer :: info\r
- end subroutine\r
-end module\r
-\r
-! { dg-final { cleanup-modules "base_mod r_mod" } }\r
+! { dg-do compile }
+!
+! PR 54190: TYPE(*)/assumed-rank: Type/rank check too relaxed for dummy procedure
+! PR 57217: [4.7/4.8/4.9 Regression][OOP] Accepts invalid TBP overriding - lacking arguments check
+!
+! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
+
+module base_mod
+ implicit none
+ type base_type
+ integer :: kind
+ contains
+ procedure, pass(map) :: clone => base_clone
+ end type
+contains
+ subroutine base_clone(map,mapout,info)
+ class(base_type), intent(inout) :: map
+ class(base_type), intent(inout) :: mapout
+ integer :: info
+ end subroutine
+end module
+
+module r_mod
+ use base_mod
+ implicit none
+ type, extends(base_type) :: r_type
+ real :: dat
+ contains
+ procedure, pass(map) :: clone => r_clone ! { dg-error "Rank mismatch in argument" }
+ end type
+contains
+ subroutine r_clone(map,mapout,info)
+ class(r_type), intent(inout) :: map
+ class(base_type), intent(inout) :: mapout(..)
+ integer :: info
+ end subroutine
+end module
-! { dg-do compile }\r
-!\r
-! PR 54190: TYPE(*)/assumed-rank: Type/rank check too relaxed for dummy procedure\r
-! PR 57217: [4.7/4.8/4.9 Regression][OOP] Accepts invalid TBP overriding - lacking arguments check\r
-!\r
-! Contributed by Tobias Burnus <burnus@gcc.gnu.org>\r
-\r
-module base_mod\r
- implicit none\r
- type base_type\r
- integer :: kind\r
- contains\r
- procedure, pass(map) :: clone => base_clone\r
- end type\r
-contains\r
- subroutine base_clone(map,mapout,info)\r
- class(base_type), intent(inout) :: map\r
- class(base_type), intent(inout) :: mapout\r
- integer :: info\r
- end subroutine\r
-end module\r
-\r
-module r_mod\r
- use base_mod\r
- implicit none\r
- type, extends(base_type) :: r_type\r
- real :: dat\r
- contains\r
- procedure, pass(map) :: clone => r_clone ! { dg-error "Type mismatch in argument" }\r
- end type\r
-contains\r
- subroutine r_clone(map,mapout,info)\r
- class(r_type), intent(inout) :: map\r
- type(*), intent(inout) :: mapout\r
- integer :: info\r
- end subroutine\r
-end module\r
-\r
-! { dg-final { cleanup-modules "base_mod r_mod" } }\r
+! { dg-do compile }
+!
+! PR 54190: TYPE(*)/assumed-rank: Type/rank check too relaxed for dummy procedure
+! PR 57217: [4.7/4.8/4.9 Regression][OOP] Accepts invalid TBP overriding - lacking arguments check
+!
+! Contributed by Tobias Burnus <burnus@gcc.gnu.org>
+
+module base_mod
+ implicit none
+ type base_type
+ integer :: kind
+ contains
+ procedure, pass(map) :: clone => base_clone
+ end type
+contains
+ subroutine base_clone(map,mapout,info)
+ class(base_type), intent(inout) :: map
+ class(base_type), intent(inout) :: mapout
+ integer :: info
+ end subroutine
+end module
+
+module r_mod
+ use base_mod
+ implicit none
+ type, extends(base_type) :: r_type
+ real :: dat
+ contains
+ procedure, pass(map) :: clone => r_clone ! { dg-error "Type mismatch in argument" }
+ end type
+contains
+ subroutine r_clone(map,mapout,info)
+ class(r_type), intent(inout) :: map
+ type(*), intent(inout) :: mapout
+ integer :: info
+ end subroutine
+end module
end function
end module
-
-! { dg-final { cleanup-modules "t" } }
type(pdf) pp
print pp%getx() ! { dg-error "must be of type default-kind CHARACTER or of INTEGER" }
end program
-
-! { dg-final { cleanup-modules "pdfs" } }
end function
end module
-
-! { dg-final { cleanup-modules "phs_single" } }
end function
end module
-
-! { dg-final { cleanup-modules "classes" } }
end function
end module
-
-! { dg-final { cleanup-modules "classes" } }
end subroutine
end
-
-! { dg-final { cleanup-modules "ObjectLists" } }
end subroutine
end module
-
-! { dg-final { cleanup-modules "IO" } }
END SELECT; END SELECT
END SUBROUTINE copy_int
END PROGRAM main
-
-! { dg-final { cleanup-modules "m" } }
end select
end do
end program main
-
-! { dg-final { cleanup-modules "list_mod link_mod" } }
& dq2, gmes
end subroutine dforceb
-! { dg-final { cleanup-modules "cell_base constants control_flags cvan electrons_base electrons_nose gvecs gvecw ions_base kinds parameters" } }
USE ISO_C_BINDING ! { dg-warning "9:has no ONLY qualifier" }
END SUBROUTINE S3
END MODULE
-! { dg-final { cleanup-modules "foo testmod" } }
print *, "Hello ", a, "!"
end subroutine
end module
-
-! { dg-final { cleanup-modules "mod_say_hello" } }
subroutine s5 ! { dg-warning "defined but not used" }
end subroutine
end
-
-! { dg-final { cleanup-modules "m" } }
proc list-module-names-1 { file } {
set result {}
- set tmp [grep $file "^\[ \t\]*((#)?\[ \t\]*include|\[mM\]\[oO\]\[dD\]\[uU\]\[lL\]\[eE\](?!\[ \t\]+\[pP\]\[rR\]\[oO\]\[cC\]\[eE\]\[dD\]\[uU\]\[rR\]\[eE\]\[ \t\]+))\[ \t\]+.*" line]
+ if {[file isdirectory $file]} {return}
+ # Find lines containing INCLUDE, MODULE, and SUBMODULE, excluding the lines containing
+ # MODULE [PURE|(IMPURE\s+)?ELEMENTAL|RECURSIVE] (PROCEDURE|FUNCTION|SUBROUTINE)
+ set pat {^\s*((#)?\s*include|(sub)?module(?!\s+((pure|(impure\s+)?elemental|recursive)\s+)?(procedure|function|subroutine)[:\s]+))\s*.*}
+ set tmp [igrep $file $pat line]
if {![string match "" $tmp]} {
foreach i $tmp {
- regexp "(\[0-9\]+)\[ \t\]+(?:(?:#)?\[ \t\]*include\[ \t\]+)\[\"\](\[^\"\]*)\[\"\]" $i dummy lineno include_file
+ regexp -nocase {(\d+)\s+#?\s*include\s+["']([^"']*)["']} $i dummy lineno include_file
if {[info exists include_file]} {
set dir [file dirname $file]
set inc "$dir/$include_file"
}
continue
}
- regexp "(\[0-9\]+)\[ \t\]+(?:(\[mM\]\[oO\]\[dD\]\[uU\]\[lL\]\[eE\]\[ \t\]+(?!\[pP\]\[rR\]\[oO\]\[cC\]\[eE\]\[dD\]\[uU\]\[rR\]\[eE\]\[ \t\]+)))(\[^ \t;\]*)" $i i lineno keyword mod
- if {![info exists lineno]} {
+ regexp -nocase {(\d+)\s+(module|submodule)\s*([^;]*)} $i i lineno keyword mod
+ if {![info exists mod]} {
continue
}
+ # Generates the file name mod_name@submod_name from
+ # (\s*mod_name[:submod_name]\s*)\s*submod_name\s*[! comment]
+ regsub {\s*!.*} $mod "" mod
+ regsub {:[^)]*} $mod "" mod
+ regsub {\(\s*} $mod "" mod
+ regsub {\s*\)\s*} $mod "@" mod
verbose "Line $lineno mentions module `$mod'" 3
if {[lsearch $result $mod] < 0} {
lappend result $mod
}
return $result
}
+
+# Looks for case insensitive occurrences of a string in a file.
+# return:list of lines that matched or NULL if none match.
+# args: first arg is the filename,
+# second is the pattern,
+# third are any options.
+# Options: line - puts line numbers of match in list
+#
+proc igrep { args } {
+
+ set file [lindex $args 0]
+ set pattern [lindex $args 1]
+
+ verbose "Grepping $file for the pattern \"$pattern\"" 3
+
+ set argc [llength $args]
+ if { $argc > 2 } {
+ for { set i 2 } { $i < $argc } { incr i } {
+ append options [lindex $args $i]
+ append options " "
+ }
+ } else {
+ set options ""
+ }
+
+ set i 0
+ set fd [open $file r]
+ while { [gets $fd cur_line]>=0 } {
+ incr i
+ if {[regexp -nocase -- "$pattern" $cur_line match]} {
+ if {![string match "" $options]} {
+ foreach opt $options {
+ switch $opt {
+ "line" {
+ lappend grep_out [concat $i $match]
+ }
+ }
+ }
+ } else {
+ lappend grep_out $match
+ }
+ }
+ }
+ close $fd
+ unset fd
+ unset i
+ if {![info exists grep_out]} {
+ set grep_out ""
+ }
+ return $grep_out
+}