summaryrefslogtreecommitdiff
path: root/numpy/f2py/tests
diff options
context:
space:
mode:
Diffstat (limited to 'numpy/f2py/tests')
-rw-r--r--numpy/f2py/tests/src/crackfortran/gh23533.f5
-rw-r--r--numpy/f2py/tests/src/crackfortran/gh23598.f904
-rw-r--r--numpy/f2py/tests/src/crackfortran/gh23598Warn.f9011
-rw-r--r--numpy/f2py/tests/src/crackfortran/unicode_comment.f904
-rw-r--r--numpy/f2py/tests/src/string/scalar_string.f909
-rw-r--r--numpy/f2py/tests/test_character.py29
-rw-r--r--numpy/f2py/tests/test_crackfortran.py78
-rw-r--r--numpy/f2py/tests/test_f2py2e.py22
-rw-r--r--numpy/f2py/tests/test_kind.py27
-rw-r--r--numpy/f2py/tests/util.py20
10 files changed, 198 insertions, 11 deletions
diff --git a/numpy/f2py/tests/src/crackfortran/gh23533.f b/numpy/f2py/tests/src/crackfortran/gh23533.f
new file mode 100644
index 000000000..db522afa7
--- /dev/null
+++ b/numpy/f2py/tests/src/crackfortran/gh23533.f
@@ -0,0 +1,5 @@
+ SUBROUTINE EXAMPLE( )
+ IF( .TRUE. ) THEN
+ CALL DO_SOMETHING()
+ END IF ! ** .TRUE. **
+ END
diff --git a/numpy/f2py/tests/src/crackfortran/gh23598.f90 b/numpy/f2py/tests/src/crackfortran/gh23598.f90
new file mode 100644
index 000000000..e0dffb5ef
--- /dev/null
+++ b/numpy/f2py/tests/src/crackfortran/gh23598.f90
@@ -0,0 +1,4 @@
+integer function intproduct(a, b) result(res)
+ integer, intent(in) :: a, b
+ res = a*b
+end function
diff --git a/numpy/f2py/tests/src/crackfortran/gh23598Warn.f90 b/numpy/f2py/tests/src/crackfortran/gh23598Warn.f90
new file mode 100644
index 000000000..3b44efc5e
--- /dev/null
+++ b/numpy/f2py/tests/src/crackfortran/gh23598Warn.f90
@@ -0,0 +1,11 @@
+module test_bug
+ implicit none
+ private
+ public :: intproduct
+
+contains
+ integer function intproduct(a, b) result(res)
+ integer, intent(in) :: a, b
+ res = a*b
+ end function
+end module
diff --git a/numpy/f2py/tests/src/crackfortran/unicode_comment.f90 b/numpy/f2py/tests/src/crackfortran/unicode_comment.f90
new file mode 100644
index 000000000..13515ce98
--- /dev/null
+++ b/numpy/f2py/tests/src/crackfortran/unicode_comment.f90
@@ -0,0 +1,4 @@
+subroutine foo(x)
+ real(8), intent(in) :: x
+ ! Écrit à l'écran la valeur de x
+end subroutine
diff --git a/numpy/f2py/tests/src/string/scalar_string.f90 b/numpy/f2py/tests/src/string/scalar_string.f90
new file mode 100644
index 000000000..f8f076172
--- /dev/null
+++ b/numpy/f2py/tests/src/string/scalar_string.f90
@@ -0,0 +1,9 @@
+MODULE string_test
+
+ character(len=8) :: string
+ character string77 * 8
+
+ character(len=12), dimension(5,7) :: strarr
+ character strarr77(5,7) * 12
+
+END MODULE string_test
diff --git a/numpy/f2py/tests/test_character.py b/numpy/f2py/tests/test_character.py
index b54b4d981..0bb0f4290 100644
--- a/numpy/f2py/tests/test_character.py
+++ b/numpy/f2py/tests/test_character.py
@@ -457,9 +457,10 @@ class TestMiscCharacter(util.F2PyTest):
character(len=*), intent(in) :: x(:)
!f2py intent(out) x
integer :: i
- do i=1, size(x)
- print*, "x(",i,")=", x(i)
- end do
+ ! Uncomment for debug printing:
+ !do i=1, size(x)
+ ! print*, "x(",i,")=", x(i)
+ !end do
end subroutine {fprefix}_gh4519
pure function {fprefix}_gh3425(x) result (y)
@@ -568,3 +569,25 @@ class TestMiscCharacter(util.F2PyTest):
assert_equal(len(a), 2)
assert_raises(Exception, lambda: f(b'c'))
+
+
+class TestStringScalarArr(util.F2PyTest):
+ sources = [util.getpath("tests", "src", "string", "scalar_string.f90")]
+
+ @pytest.mark.slow
+ def test_char(self):
+ for out in (self.module.string_test.string,
+ self.module.string_test.string77):
+ expected = ()
+ assert out.shape == expected
+ expected = '|S8'
+ assert out.dtype == expected
+
+ @pytest.mark.slow
+ def test_char_arr(self):
+ for out in (self.module.string_test.strarr,
+ self.module.string_test.strarr77):
+ expected = (5,7)
+ assert out.shape == expected
+ expected = '|S12'
+ assert out.dtype == expected
diff --git a/numpy/f2py/tests/test_crackfortran.py b/numpy/f2py/tests/test_crackfortran.py
index dcf8760db..49bfc13af 100644
--- a/numpy/f2py/tests/test_crackfortran.py
+++ b/numpy/f2py/tests/test_crackfortran.py
@@ -1,7 +1,10 @@
+import importlib
import codecs
+import time
+import unicodedata
import pytest
import numpy as np
-from numpy.f2py.crackfortran import markinnerspaces
+from numpy.f2py.crackfortran import markinnerspaces, nameargspattern
from . import util
from numpy.f2py import crackfortran
import textwrap
@@ -132,6 +135,7 @@ class TestMarkinnerspaces:
assert markinnerspaces("a 'b c' 'd e'") == "a 'b@_@c' 'd@_@e'"
assert markinnerspaces(r'a "b c" "d e"') == r'a "b@_@c" "d@_@e"'
+
class TestDimSpec(util.F2PyTest):
"""This test suite tests various expressions that are used as dimension
specifications.
@@ -241,6 +245,7 @@ class TestModuleDeclaration:
assert len(mod) == 1
assert mod[0]["vars"]["abar"]["="] == "bar('abar')"
+
class TestEval(util.F2PyTest):
def test_eval_scalar(self):
eval_scalar = crackfortran._eval_scalar
@@ -257,13 +262,76 @@ class TestFortranReader(util.F2PyTest):
def test_input_encoding(self, tmp_path, encoding):
# gh-635
f_path = tmp_path / f"input_with_{encoding}_encoding.f90"
- # explicit BOM is required for UTF8
- bom = {'utf-8': codecs.BOM_UTF8}.get(encoding, b'')
with f_path.open('w', encoding=encoding) as ff:
- ff.write(bom.decode(encoding) +
- """
+ ff.write("""
subroutine foo()
end subroutine foo
""")
mod = crackfortran.crackfortran([str(f_path)])
assert mod[0]['name'] == 'foo'
+
+
+class TestUnicodeComment(util.F2PyTest):
+ sources = [util.getpath("tests", "src", "crackfortran", "unicode_comment.f90")]
+
+ @pytest.mark.skipif(
+ (importlib.util.find_spec("charset_normalizer") is None),
+ reason="test requires charset_normalizer which is not installed",
+ )
+ def test_encoding_comment(self):
+ self.module.foo(3)
+
+
+class TestNameArgsPatternBacktracking:
+ @pytest.mark.parametrize(
+ ['adversary'],
+ [
+ ('@)@bind@(@',),
+ ('@)@bind @(@',),
+ ('@)@bind foo bar baz@(@',)
+ ]
+ )
+ def test_nameargspattern_backtracking(self, adversary):
+ '''address ReDOS vulnerability:
+ https://github.com/numpy/numpy/issues/23338'''
+ trials_per_batch = 12
+ batches_per_regex = 4
+ start_reps, end_reps = 15, 25
+ for ii in range(start_reps, end_reps):
+ repeated_adversary = adversary * ii
+ # test times in small batches.
+ # this gives us more chances to catch a bad regex
+ # while still catching it before too long if it is bad
+ for _ in range(batches_per_regex):
+ times = []
+ for _ in range(trials_per_batch):
+ t0 = time.perf_counter()
+ mtch = nameargspattern.search(repeated_adversary)
+ times.append(time.perf_counter() - t0)
+ # our pattern should be much faster than 0.2s per search
+ # it's unlikely that a bad regex will pass even on fast CPUs
+ assert np.median(times) < 0.2
+ assert not mtch
+ # if the adversary is capped with @)@, it becomes acceptable
+ # according to the old version of the regex.
+ # that should still be true.
+ good_version_of_adversary = repeated_adversary + '@)@'
+ assert nameargspattern.search(good_version_of_adversary)
+
+
+class TestFunctionReturn(util.F2PyTest):
+ sources = [util.getpath("tests", "src", "crackfortran", "gh23598.f90")]
+
+ def test_function_rettype(self):
+ # gh-23598
+ assert self.module.intproduct(3, 4) == 12
+
+
+class TestFortranGroupCounters(util.F2PyTest):
+ def test_end_if_comment(self):
+ # gh-23533
+ fpath = util.getpath("tests", "src", "crackfortran", "gh23533.f")
+ try:
+ crackfortran.crackfortran([str(fpath)])
+ except Exception as exc:
+ assert False, f"'crackfortran.crackfortran' raised an exception {exc}"
diff --git a/numpy/f2py/tests/test_f2py2e.py b/numpy/f2py/tests/test_f2py2e.py
index 2c10f046f..5f7b56a68 100644
--- a/numpy/f2py/tests/test_f2py2e.py
+++ b/numpy/f2py/tests/test_f2py2e.py
@@ -63,6 +63,15 @@ def hello_world_f90(tmpdir_factory):
@pytest.fixture(scope="session")
+def gh23598_warn(tmpdir_factory):
+ """F90 file for testing warnings in gh23598"""
+ fdat = util.getpath("tests", "src", "crackfortran", "gh23598Warn.f90").read_text()
+ fn = tmpdir_factory.getbasetemp() / "gh23598Warn.f90"
+ fn.write_text(fdat, encoding="ascii")
+ return fn
+
+
+@pytest.fixture(scope="session")
def hello_world_f77(tmpdir_factory):
"""Generates a single f77 file for testing"""
fdat = util.getpath("tests", "src", "cli", "hi77.f").read_text()
@@ -91,6 +100,19 @@ def f2cmap_f90(tmpdir_factory):
return fn
+def test_gh23598_warn(capfd, gh23598_warn, monkeypatch):
+ foutl = get_io_paths(gh23598_warn, mname="test")
+ ipath = foutl.f90inp
+ monkeypatch.setattr(
+ sys, "argv",
+ f'f2py {ipath} -m test'.split())
+
+ with util.switchdir(ipath.parent):
+ f2pycli() # Generate files
+ wrapper = foutl.wrap90.read_text()
+ assert "intproductf2pywrap, intpr" not in wrapper
+
+
def test_gen_pyf(capfd, hello_world_f90, monkeypatch):
"""Ensures that a signature file is generated via the CLI
CLI :: -h
diff --git a/numpy/f2py/tests/test_kind.py b/numpy/f2py/tests/test_kind.py
index f0cb61fb6..69b85aaad 100644
--- a/numpy/f2py/tests/test_kind.py
+++ b/numpy/f2py/tests/test_kind.py
@@ -1,5 +1,6 @@
import os
import pytest
+import platform
from numpy.f2py.crackfortran import (
_selected_int_kind_func as selected_int_kind,
@@ -11,8 +12,8 @@ from . import util
class TestKind(util.F2PyTest):
sources = [util.getpath("tests", "src", "kind", "foo.f90")]
- def test_all(self):
- selectedrealkind = self.module.selectedrealkind
+ def test_int(self):
+ """Test `int` kind_func for integers up to 10**40."""
selectedintkind = self.module.selectedintkind
for i in range(40):
@@ -20,7 +21,27 @@ class TestKind(util.F2PyTest):
i
), f"selectedintkind({i}): expected {selected_int_kind(i)!r} but got {selectedintkind(i)!r}"
- for i in range(20):
+ def test_real(self):
+ """
+ Test (processor-dependent) `real` kind_func for real numbers
+ of up to 31 digits precision (extended/quadruple).
+ """
+ selectedrealkind = self.module.selectedrealkind
+
+ for i in range(32):
+ assert selectedrealkind(i) == selected_real_kind(
+ i
+ ), f"selectedrealkind({i}): expected {selected_real_kind(i)!r} but got {selectedrealkind(i)!r}"
+
+ @pytest.mark.xfail(platform.machine().lower().startswith("ppc"),
+ reason="Some PowerPC may not support full IEEE 754 precision")
+ def test_quad_precision(self):
+ """
+ Test kind_func for quadruple precision [`real(16)`] of 32+ digits .
+ """
+ selectedrealkind = self.module.selectedrealkind
+
+ for i in range(32, 40):
assert selectedrealkind(i) == selected_real_kind(
i
), f"selectedrealkind({i}): expected {selected_real_kind(i)!r} but got {selectedrealkind(i)!r}"
diff --git a/numpy/f2py/tests/util.py b/numpy/f2py/tests/util.py
index 1534c4e7d..26fa7e49d 100644
--- a/numpy/f2py/tests/util.py
+++ b/numpy/f2py/tests/util.py
@@ -6,6 +6,7 @@ Utility functions for
- determining paths to tests
"""
+import glob
import os
import sys
import subprocess
@@ -30,6 +31,10 @@ from importlib import import_module
_module_dir = None
_module_num = 5403
+if sys.platform == "cygwin":
+ NUMPY_INSTALL_ROOT = Path(__file__).parent.parent.parent
+ _module_list = list(NUMPY_INSTALL_ROOT.glob("**/*.dll"))
+
def _cleanup():
global _module_dir
@@ -147,6 +152,21 @@ def build_module(source_files, options=[], skip=[], only=[], module_name=None):
for fn in dst_sources:
os.unlink(fn)
+ # Rebase (Cygwin-only)
+ if sys.platform == "cygwin":
+ # If someone starts deleting modules after import, this will
+ # need to change to record how big each module is, rather than
+ # relying on rebase being able to find that from the files.
+ _module_list.extend(
+ glob.glob(os.path.join(d, "{:s}*".format(module_name)))
+ )
+ subprocess.check_call(
+ ["/usr/bin/rebase", "--database", "--oblivious", "--verbose"]
+ + _module_list
+ )
+
+
+
# Import
return import_module(module_name)