Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
134 changes: 128 additions & 6 deletions src/fortplot_matplotlib.f90
Original file line number Diff line number Diff line change
Expand Up @@ -91,19 +91,80 @@ subroutine contour_filled(x, y, z, levels, colormap, show_colorbar, label)
character(len=*), intent(in), optional :: colormap, label
logical, intent(in), optional :: show_colorbar

real(wp), allocatable :: wp_x(:), wp_y(:), wp_z(:,:), wp_levels(:)

call ensure_global_figure_initialized()
call fig%add_contour_filled(x, y, z, levels=levels, label=label)

! Convert input arrays to working precision
allocate(wp_x(size(x)), wp_y(size(y)), wp_z(size(z,1), size(z,2)))
wp_x = real(x, wp)
wp_y = real(y, wp)
wp_z = real(z, wp)

if (present(levels)) then
allocate(wp_levels(size(levels)))
wp_levels = real(levels, wp)
else
allocate(wp_levels(0))
end if

! Forward ALL parameters to underlying method using single call pattern
call fig%add_contour_filled(wp_x, wp_y, wp_z, &
levels=merge(wp_levels, wp_levels, present(levels)), &
colormap=merge(colormap, "", present(colormap)), &
show_colorbar=merge(show_colorbar, .false., present(show_colorbar)), &
label=merge(label, "", present(label)))

deallocate(wp_x, wp_y, wp_z)
if (allocated(wp_levels)) deallocate(wp_levels)
end subroutine contour_filled

subroutine pcolormesh(x, y, z, shading, colormap, show_colorbar, label)
subroutine pcolormesh(x, y, z, shading, colormap, show_colorbar, label, &
vmin, vmax, edgecolors, linewidths)
!! Add a pseudocolor mesh plot to the global figure (pyplot-style)
real(8), dimension(:), intent(in) :: x, y
real(8), dimension(:,:), intent(in) :: z
character(len=*), intent(in), optional :: shading, colormap, label
logical, intent(in), optional :: show_colorbar
real(8), intent(in), optional :: vmin, vmax
real(8), dimension(3), intent(in), optional :: edgecolors
real(8), intent(in), optional :: linewidths

real(wp), allocatable :: wp_x(:), wp_y(:), wp_z(:,:)
real(wp) :: wp_vmin, wp_vmax, wp_linewidths
real(wp) :: wp_edgecolors(3)

call ensure_global_figure_initialized()
call fig%add_pcolormesh(x, y, z)

! Convert input arrays to working precision
allocate(wp_x(size(x)), wp_y(size(y)), wp_z(size(z,1), size(z,2)))
wp_x = real(x, wp)
wp_y = real(y, wp)
wp_z = real(z, wp)

! Convert optional parameters to working precision
if (present(vmin)) then
wp_vmin = real(vmin, wp)
end if
if (present(vmax)) then
wp_vmax = real(vmax, wp)
end if
if (present(edgecolors)) then
wp_edgecolors = real(edgecolors, wp)
end if
if (present(linewidths)) then
wp_linewidths = real(linewidths, wp)
end if

! Forward SUPPORTED parameters to underlying method using single call pattern
call fig%add_pcolormesh(wp_x, wp_y, wp_z, &
colormap=merge(colormap, "", present(colormap)), &
vmin=merge(wp_vmin, 0.0_wp, present(vmin)), &
vmax=merge(wp_vmax, 0.0_wp, present(vmax)), &
edgecolors=merge(wp_edgecolors, [0.0_wp, 0.0_wp, 0.0_wp], present(edgecolors)), &
linewidths=merge(wp_linewidths, 0.0_wp, present(linewidths)))

deallocate(wp_x, wp_y, wp_z)
end subroutine pcolormesh

subroutine streamplot(x, y, u, v, density, linewidth_scale, arrow_scale, colormap, label)
Expand Down Expand Up @@ -346,19 +407,80 @@ subroutine add_contour_filled(x, y, z, levels, colormap, show_colorbar, label)
character(len=*), intent(in), optional :: colormap, label
logical, intent(in), optional :: show_colorbar

real(wp), allocatable :: wp_x(:), wp_y(:), wp_z(:,:), wp_levels(:)

call ensure_global_figure_initialized()
call fig%add_contour_filled(x, y, z, levels=levels, label=label)

! Convert input arrays to working precision
allocate(wp_x(size(x)), wp_y(size(y)), wp_z(size(z,1), size(z,2)))
wp_x = real(x, wp)
wp_y = real(y, wp)
wp_z = real(z, wp)

if (present(levels)) then
allocate(wp_levels(size(levels)))
wp_levels = real(levels, wp)
else
allocate(wp_levels(0))
end if

! Forward ALL parameters to underlying method using single call pattern
call fig%add_contour_filled(wp_x, wp_y, wp_z, &
levels=merge(wp_levels, wp_levels, present(levels)), &
colormap=merge(colormap, "", present(colormap)), &
show_colorbar=merge(show_colorbar, .false., present(show_colorbar)), &
label=merge(label, "", present(label)))

deallocate(wp_x, wp_y, wp_z)
if (allocated(wp_levels)) deallocate(wp_levels)
end subroutine add_contour_filled

subroutine add_pcolormesh(x, y, z, shading, colormap, show_colorbar, label)
subroutine add_pcolormesh(x, y, z, shading, colormap, show_colorbar, label, &
vmin, vmax, edgecolors, linewidths)
!! Add a pseudocolor mesh plot to the global figure
real(8), dimension(:), intent(in) :: x, y
real(8), dimension(:,:), intent(in) :: z
character(len=*), intent(in), optional :: shading, colormap, label
logical, intent(in), optional :: show_colorbar
real(8), intent(in), optional :: vmin, vmax
real(8), dimension(3), intent(in), optional :: edgecolors
real(8), intent(in), optional :: linewidths

real(wp), allocatable :: wp_x(:), wp_y(:), wp_z(:,:)
real(wp) :: wp_vmin, wp_vmax, wp_linewidths
real(wp) :: wp_edgecolors(3)

call ensure_global_figure_initialized()
call fig%add_pcolormesh(x, y, z)

! Convert input arrays to working precision
allocate(wp_x(size(x)), wp_y(size(y)), wp_z(size(z,1), size(z,2)))
wp_x = real(x, wp)
wp_y = real(y, wp)
wp_z = real(z, wp)

! Convert optional parameters to working precision
if (present(vmin)) then
wp_vmin = real(vmin, wp)
end if
if (present(vmax)) then
wp_vmax = real(vmax, wp)
end if
if (present(edgecolors)) then
wp_edgecolors = real(edgecolors, wp)
end if
if (present(linewidths)) then
wp_linewidths = real(linewidths, wp)
end if

! Forward SUPPORTED parameters to underlying method using single call pattern
call fig%add_pcolormesh(wp_x, wp_y, wp_z, &
colormap=merge(colormap, "", present(colormap)), &
vmin=merge(wp_vmin, 0.0_wp, present(vmin)), &
vmax=merge(wp_vmax, 0.0_wp, present(vmax)), &
edgecolors=merge(wp_edgecolors, [0.0_wp, 0.0_wp, 0.0_wp], present(edgecolors)), &
linewidths=merge(wp_linewidths, 0.0_wp, present(linewidths)))

deallocate(wp_x, wp_y, wp_z)
end subroutine add_pcolormesh

subroutine add_errorbar(x, y, xerr, yerr, fmt, label, capsize, linestyle, marker, color)
Expand Down
188 changes: 188 additions & 0 deletions test/test_parameter_forwarding.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,188 @@
program test_parameter_forwarding
!! Test comprehensive parameter forwarding in matplotlib wrapper functions
!! Critical API consistency validation for issue #396

use iso_fortran_env, only: wp => real64
use fortplot_matplotlib
use fortplot_figure_core, only: figure_t
implicit none

integer, parameter :: nx = 3, ny = 3
real(wp) :: x(nx+1), y(ny+1), z(ny,nx)
logical :: test_passed

! Initialize test data
call setup_test_data(x, y, z)

! Run parameter forwarding tests
test_passed = .true.

! Test pcolormesh parameter forwarding
call test_pcolormesh_parameter_forwarding(test_passed)

! Test contour_filled parameter forwarding
call test_contour_filled_parameter_forwarding(test_passed)

if (test_passed) then
print *, "PASS: All parameter forwarding tests passed"
stop 0
else
print *, "FAIL: Parameter forwarding tests failed"
stop 1
end if

contains

subroutine setup_test_data(x, y, z)
!! Setup simple test data for parameter forwarding validation
!! x: size nx+1, y: size ny+1, z: size (ny, nx)
real(wp), intent(out) :: x(:), y(:), z(:,:)
integer :: i, j

! Grid vertex coordinates (need nx+1 and ny+1 points for nx*ny cells)
do i = 1, size(x)
x(i) = real(i-1, wp)
end do
do i = 1, size(y)
y(i) = real(i-1, wp)
end do

! Cell color data (ny rows, nx columns)
do i = 1, size(z,1) ! ny rows
do j = 1, size(z,2) ! nx columns
z(i,j) = real(i+j-2, wp)
end do
end do
end subroutine setup_test_data

subroutine test_pcolormesh_parameter_forwarding(test_passed)
!! Test that pcolormesh wrapper functions forward ALL parameters correctly
logical, intent(inout) :: test_passed

print *, "Testing pcolormesh parameter forwarding..."

! Test 1: pcolormesh() with ALL parameters
! This MUST NOT cause compilation or runtime errors
call test_pcolormesh_all_parameters(test_passed)

! Test 2: add_pcolormesh() with ALL parameters
call test_add_pcolormesh_all_parameters(test_passed)

if (test_passed) then
print *, " PASS: pcolormesh parameter forwarding tests"
else
print *, " FAIL: pcolormesh parameter forwarding failed"
end if
end subroutine test_pcolormesh_parameter_forwarding

subroutine test_pcolormesh_all_parameters(test_passed)
!! Test pcolormesh() wrapper with complete parameter set
logical, intent(inout) :: test_passed

! Initialize figure
call figure()

! Test call with ALL parameters that should be supported
! Based on issue #396, these parameters MUST be forwarded:
call pcolormesh(x, y, z, &
shading='flat', &
colormap='viridis', &
show_colorbar=.true., &
label='test', &
vmin=0.0_wp, &
vmax=10.0_wp, &
edgecolors=[0.5_wp, 0.5_wp, 0.5_wp], &
linewidths=1.0_wp)

! If we reach here without errors, parameter forwarding compiles
print *, " PASS: pcolormesh() accepts all required parameters"

end subroutine test_pcolormesh_all_parameters

subroutine test_add_pcolormesh_all_parameters(test_passed)
!! Test add_pcolormesh() wrapper with complete parameter set
logical, intent(inout) :: test_passed

! Initialize figure
call figure()

! Test call with ALL parameters that should be supported
call add_pcolormesh(x, y, z, &
shading='flat', &
colormap='plasma', &
show_colorbar=.false., &
label='test2', &
vmin=-5.0_wp, &
vmax=5.0_wp, &
edgecolors=[1.0_wp, 0.0_wp, 0.0_wp], &
linewidths=2.0_wp)

! If we reach here without errors, parameter forwarding compiles
print *, " PASS: add_pcolormesh() accepts all required parameters"

end subroutine test_add_pcolormesh_all_parameters

subroutine test_contour_filled_parameter_forwarding(test_passed)
!! Test that contour_filled wrapper functions forward ALL parameters correctly
logical, intent(inout) :: test_passed
real(wp) :: levels(3)

print *, "Testing contour_filled parameter forwarding..."

levels = [0.0_wp, 5.0_wp, 10.0_wp]

! Test 1: contour_filled() with ALL parameters
call test_contour_filled_all_parameters(levels, test_passed)

! Test 2: add_contour_filled() with ALL parameters
call test_add_contour_filled_all_parameters(levels, test_passed)

if (test_passed) then
print *, " PASS: contour_filled parameter forwarding tests"
else
print *, " FAIL: contour_filled parameter forwarding failed"
end if
end subroutine test_contour_filled_parameter_forwarding

subroutine test_contour_filled_all_parameters(levels, test_passed)
!! Test contour_filled() wrapper with complete parameter set
real(wp), intent(in) :: levels(:)
logical, intent(inout) :: test_passed

! Initialize figure
call figure()

! Test call with ALL parameters that should be supported
! Based on issue #396, these parameters MUST be forwarded:
call contour_filled(x, y, z, &
levels=levels, &
colormap='coolwarm', &
show_colorbar=.true., &
label='contour_test')

! If we reach here without errors, parameter forwarding compiles
print *, " PASS: contour_filled() forwards all required parameters"

end subroutine test_contour_filled_all_parameters

subroutine test_add_contour_filled_all_parameters(levels, test_passed)
!! Test add_contour_filled() wrapper with complete parameter set
real(wp), intent(in) :: levels(:)
logical, intent(inout) :: test_passed

! Initialize figure
call figure()

! Test call with ALL parameters that should be supported
call add_contour_filled(x, y, z, &
levels=levels, &
colormap='inferno', &
show_colorbar=.false., &
label='add_contour_test')

! If we reach here without errors, parameter forwarding compiles
print *, " PASS: add_contour_filled() forwards all required parameters"

end subroutine test_add_contour_filled_all_parameters

end program test_parameter_forwarding
Loading