Skip to content

Commit 0878dbb

Browse files
krystophnyclaude
andcommitted
refactor: complete symlog tick generation implementation
- Implement add_negative_symlog_ticks for negative logarithmic region - Implement add_linear_symlog_ticks for linear region around zero - Implement add_positive_symlog_ticks for positive logarithmic region - Add comprehensive edge case tests for all symlog regions - Fix boundary conditions to avoid tick overlap between regions - Ensure smooth transitions and proper tick placement Fixes #342 🤖 Generated with [Claude Code](https://claude.ai/code) Co-Authored-By: Claude <noreply@anthropic.com>
1 parent b9de47b commit 0878dbb

File tree

2 files changed

+303
-14
lines changed

2 files changed

+303
-14
lines changed

src/fortplot_axes.f90

Lines changed: 77 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -119,8 +119,8 @@ subroutine compute_symlog_ticks(data_min, data_max, threshold, tick_positions, n
119119
call add_negative_symlog_ticks(data_min, -threshold, tick_positions, num_ticks)
120120
end if
121121

122-
! Add linear region ticks
123-
if (data_min <= threshold .and. data_max >= -threshold) then
122+
! Add linear region ticks (only for the region within threshold bounds)
123+
if (max(data_min, -threshold) <= min(data_max, threshold)) then
124124
call add_linear_symlog_ticks(max(data_min, -threshold), min(data_max, threshold), &
125125
tick_positions, num_ticks)
126126
end if
@@ -193,39 +193,102 @@ function calculate_nice_step(raw_step) result(nice_step)
193193
end function calculate_nice_step
194194

195195
subroutine add_negative_symlog_ticks(data_min, upper_bound, tick_positions, num_ticks)
196+
!! Add ticks for negative logarithmic region of symlog scale
196197
real(wp), intent(in) :: data_min, upper_bound
197198
real(wp), intent(inout) :: tick_positions(MAX_TICKS)
198199
integer, intent(inout) :: num_ticks
199200

200-
! Suppress unused parameter warnings for stub implementation
201-
associate(unused_real => data_min + upper_bound, &
202-
unused_arr => tick_positions, unused_int => num_ticks); end associate
201+
real(wp) :: log_min, log_max, current_power
202+
integer :: start_power, end_power, power
203+
204+
if (data_min >= 0.0_wp .or. upper_bound >= 0.0_wp .or. upper_bound <= data_min) return
205+
206+
! Work with positive values for log calculations
207+
! For negative range [-500, -1], we want powers that give us ticks in that range
208+
log_min = log10(-upper_bound) ! log10(1) = 0 (closer to zero)
209+
log_max = log10(-data_min) ! log10(500) = ~2.7 (larger magnitude)
210+
211+
start_power = floor(log_min)
212+
end_power = ceiling(log_max)
203213

204-
! Implementation for negative symlog region (placeholder)
214+
do power = start_power, end_power
215+
if (num_ticks >= MAX_TICKS) exit
216+
current_power = -(10.0_wp**power)
217+
218+
! Check if tick is within bounds, excluding threshold boundary
219+
if (current_power >= data_min - 1.0e-10_wp .and. &
220+
current_power < upper_bound - 1.0e-10_wp) then
221+
num_ticks = num_ticks + 1
222+
tick_positions(num_ticks) = current_power
223+
end if
224+
end do
205225
end subroutine add_negative_symlog_ticks
206226

207227
subroutine add_linear_symlog_ticks(lower_bound, upper_bound, tick_positions, num_ticks)
228+
!! Add ticks for linear region of symlog scale
208229
real(wp), intent(in) :: lower_bound, upper_bound
209230
real(wp), intent(inout) :: tick_positions(MAX_TICKS)
210231
integer, intent(inout) :: num_ticks
211232

212-
! Suppress unused parameter warnings for stub implementation
213-
associate(unused_real => lower_bound + upper_bound, &
214-
unused_arr => tick_positions, unused_int => num_ticks); end associate
233+
real(wp) :: range, step, tick_value
234+
integer :: max_linear_ticks, i
235+
236+
if (upper_bound <= lower_bound) return
237+
238+
range = upper_bound - lower_bound
239+
max_linear_ticks = 5 ! Reasonable number for linear region
240+
241+
! Always include zero if it's in the range
242+
if (lower_bound <= 0.0_wp .and. upper_bound >= 0.0_wp .and. num_ticks < MAX_TICKS) then
243+
num_ticks = num_ticks + 1
244+
tick_positions(num_ticks) = 0.0_wp
245+
end if
246+
247+
! Add additional linear ticks
248+
step = range / real(max_linear_ticks + 1, wp)
249+
step = calculate_nice_step(step)
215250

216-
! Implementation for linear symlog region (placeholder)
251+
! Find first tick >= lower_bound
252+
tick_value = ceiling(lower_bound / step) * step
253+
254+
do while (tick_value <= upper_bound .and. num_ticks < MAX_TICKS)
255+
! Skip zero if already added, avoid duplicates
256+
if (abs(tick_value) > 1.0e-10_wp) then
257+
num_ticks = num_ticks + 1
258+
tick_positions(num_ticks) = tick_value
259+
end if
260+
tick_value = tick_value + step
261+
end do
217262
end subroutine add_linear_symlog_ticks
218263

219264
subroutine add_positive_symlog_ticks(lower_bound, data_max, tick_positions, num_ticks)
265+
!! Add ticks for positive logarithmic region of symlog scale
220266
real(wp), intent(in) :: lower_bound, data_max
221267
real(wp), intent(inout) :: tick_positions(MAX_TICKS)
222268
integer, intent(inout) :: num_ticks
223269

224-
! Suppress unused parameter warnings for stub implementation
225-
associate(unused_real => lower_bound + data_max, &
226-
unused_arr => tick_positions, unused_int => num_ticks); end associate
270+
real(wp) :: log_min, log_max, current_power
271+
integer :: start_power, end_power, power
272+
273+
if (lower_bound <= 0.0_wp .or. data_max <= 0.0_wp) return
227274

228-
! Implementation for positive symlog region (placeholder)
275+
log_min = log10(lower_bound)
276+
log_max = log10(data_max)
277+
278+
start_power = floor(log_min)
279+
end_power = ceiling(log_max)
280+
281+
do power = start_power, end_power
282+
if (num_ticks >= MAX_TICKS) exit
283+
current_power = 10.0_wp**power
284+
285+
! Check if tick is within bounds, excluding threshold boundary
286+
if (current_power > lower_bound + 1.0e-10_wp .and. &
287+
current_power <= data_max + 1.0e-10_wp) then
288+
num_ticks = num_ticks + 1
289+
tick_positions(num_ticks) = current_power
290+
end if
291+
end do
229292
end subroutine add_positive_symlog_ticks
230293

231294
function is_power_of_ten(value) result(is_power)
Lines changed: 226 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,226 @@
1+
program test_symlog_axes_implementation
2+
!! Test symlog tick generation implementation in fortplot_axes module
3+
!! Tests edge cases and proper region handling for symmetric logarithmic scale
4+
use, intrinsic :: iso_fortran_env, only: wp => real64
5+
use fortplot_axes, only: compute_scale_ticks, MAX_TICKS
6+
implicit none
7+
8+
call test_symlog_all_positive()
9+
call test_symlog_all_negative()
10+
call test_symlog_spanning_zero()
11+
call test_symlog_small_threshold()
12+
call test_symlog_large_threshold()
13+
call test_symlog_edge_boundaries()
14+
call test_symlog_single_region_cases()
15+
16+
print *, "All symlog axes implementation tests passed!"
17+
18+
contains
19+
20+
subroutine test_symlog_all_positive()
21+
!! Test symlog with all positive values
22+
real(wp) :: tick_positions(MAX_TICKS)
23+
integer :: num_ticks
24+
real(wp), parameter :: threshold = 10.0_wp
25+
26+
call compute_scale_ticks('symlog', 1.0_wp, 1000.0_wp, threshold, tick_positions, num_ticks)
27+
28+
if (num_ticks < 2) then
29+
print *, "FAIL: symlog all positive should generate multiple ticks"
30+
print *, "Got", num_ticks, "ticks for range 1 to 1000 with threshold", threshold
31+
stop 1
32+
end if
33+
34+
! Should have ticks in positive log region only
35+
if (any(tick_positions(1:num_ticks) <= 0.0_wp)) then
36+
print *, "FAIL: symlog all positive should not have negative ticks"
37+
stop 1
38+
end if
39+
40+
! Should include values > threshold in log region
41+
if (.not. any(tick_positions(1:num_ticks) > threshold)) then
42+
print *, "FAIL: symlog all positive should have ticks in log region"
43+
stop 1
44+
end if
45+
end subroutine test_symlog_all_positive
46+
47+
subroutine test_symlog_all_negative()
48+
!! Test symlog with all negative values
49+
real(wp) :: tick_positions(MAX_TICKS)
50+
integer :: num_ticks, i
51+
real(wp), parameter :: threshold = 5.0_wp
52+
53+
call compute_scale_ticks('symlog', -500.0_wp, -1.0_wp, threshold, tick_positions, num_ticks)
54+
55+
if (num_ticks < 2) then
56+
print *, "FAIL: symlog all negative should generate multiple ticks"
57+
print *, "Got", num_ticks, "ticks for range -500 to -1 with threshold", threshold
58+
stop 1
59+
end if
60+
61+
! Should have only negative ticks
62+
if (any(tick_positions(1:num_ticks) >= 0.0_wp)) then
63+
print *, "FAIL: symlog all negative should not have positive ticks"
64+
stop 1
65+
end if
66+
67+
! Should include values < -threshold in negative log region
68+
if (.not. any(tick_positions(1:num_ticks) < -threshold)) then
69+
print *, "FAIL: symlog all negative should have ticks in negative log region"
70+
print *, "No ticks found < -threshold (", -threshold, ")"
71+
stop 1
72+
end if
73+
end subroutine test_symlog_all_negative
74+
75+
subroutine test_symlog_spanning_zero()
76+
!! Test symlog spanning zero (most common case)
77+
real(wp) :: tick_positions(MAX_TICKS)
78+
integer :: num_ticks
79+
real(wp), parameter :: threshold = 1.0_wp
80+
81+
call compute_scale_ticks('symlog', -100.0_wp, 100.0_wp, threshold, tick_positions, num_ticks)
82+
83+
if (num_ticks < 3) then
84+
print *, "FAIL: symlog spanning zero should generate many ticks"
85+
print *, "Got", num_ticks, "ticks for range -100 to 100 with threshold", threshold
86+
stop 1
87+
end if
88+
89+
! Should have ticks in all three regions
90+
if (.not. any(tick_positions(1:num_ticks) < -threshold)) then
91+
print *, "FAIL: symlog spanning zero should have negative log region ticks"
92+
stop 1
93+
end if
94+
95+
if (.not. any(abs(tick_positions(1:num_ticks)) <= threshold)) then
96+
print *, "FAIL: symlog spanning zero should have linear region ticks"
97+
stop 1
98+
end if
99+
100+
if (.not. any(tick_positions(1:num_ticks) > threshold)) then
101+
print *, "FAIL: symlog spanning zero should have positive log region ticks"
102+
stop 1
103+
end if
104+
end subroutine test_symlog_spanning_zero
105+
106+
subroutine test_symlog_small_threshold()
107+
!! Test symlog with very small threshold
108+
real(wp) :: tick_positions(MAX_TICKS)
109+
integer :: num_ticks
110+
real(wp), parameter :: threshold = 0.1_wp
111+
112+
call compute_scale_ticks('symlog', -10.0_wp, 10.0_wp, threshold, tick_positions, num_ticks)
113+
114+
if (num_ticks < 2) then
115+
print *, "FAIL: symlog small threshold should generate ticks"
116+
print *, "Got", num_ticks, "ticks for range -10 to 10 with threshold", threshold
117+
stop 1
118+
end if
119+
120+
! With small threshold, most data should be in log regions
121+
if (.not. any(tick_positions(1:num_ticks) < -threshold)) then
122+
print *, "FAIL: symlog small threshold should have negative log ticks"
123+
stop 1
124+
end if
125+
126+
if (.not. any(tick_positions(1:num_ticks) > threshold)) then
127+
print *, "FAIL: symlog small threshold should have positive log ticks"
128+
stop 1
129+
end if
130+
end subroutine test_symlog_small_threshold
131+
132+
subroutine test_symlog_large_threshold()
133+
!! Test symlog with large threshold
134+
real(wp) :: tick_positions(MAX_TICKS)
135+
integer :: num_ticks
136+
real(wp), parameter :: threshold = 50.0_wp
137+
138+
call compute_scale_ticks('symlog', -10.0_wp, 10.0_wp, threshold, tick_positions, num_ticks)
139+
140+
if (num_ticks < 2) then
141+
print *, "FAIL: symlog large threshold should generate ticks"
142+
print *, "Got", num_ticks, "ticks for range -10 to 10 with threshold", threshold
143+
stop 1
144+
end if
145+
146+
! With large threshold, all data should be in linear region
147+
if (any(abs(tick_positions(1:num_ticks)) > threshold)) then
148+
print *, "FAIL: symlog large threshold should only have linear region ticks"
149+
print *, "Found tick outside threshold:", maxval(abs(tick_positions(1:num_ticks)))
150+
stop 1
151+
end if
152+
end subroutine test_symlog_large_threshold
153+
154+
subroutine test_symlog_edge_boundaries()
155+
!! Test symlog at exact threshold boundaries
156+
real(wp) :: tick_positions(MAX_TICKS)
157+
integer :: num_ticks
158+
real(wp), parameter :: threshold = 10.0_wp
159+
160+
! Data range exactly at boundaries
161+
call compute_scale_ticks('symlog', -threshold, threshold, threshold, tick_positions, num_ticks)
162+
163+
if (num_ticks < 1) then
164+
print *, "FAIL: symlog at boundaries should generate ticks"
165+
print *, "Got", num_ticks, "ticks for boundary case"
166+
stop 1
167+
end if
168+
169+
! All ticks should be within or at threshold boundaries
170+
if (any(tick_positions(1:num_ticks) < -threshold - 1.0e-10_wp) .or. &
171+
any(tick_positions(1:num_ticks) > threshold + 1.0e-10_wp)) then
172+
print *, "FAIL: symlog boundary ticks should be within threshold"
173+
stop 1
174+
end if
175+
end subroutine test_symlog_edge_boundaries
176+
177+
subroutine test_symlog_single_region_cases()
178+
!! Test symlog cases that only touch single regions
179+
real(wp) :: tick_positions(MAX_TICKS)
180+
integer :: num_ticks, i
181+
real(wp), parameter :: threshold = 1.0_wp
182+
183+
! Test only linear region
184+
call compute_scale_ticks('symlog', -0.5_wp, 0.5_wp, threshold, tick_positions, num_ticks)
185+
186+
if (num_ticks < 1) then
187+
print *, "FAIL: symlog linear-only should generate ticks"
188+
stop 1
189+
end if
190+
191+
! All ticks should be in linear region
192+
if (any(abs(tick_positions(1:num_ticks)) > threshold)) then
193+
print *, "FAIL: symlog linear-only should only have linear ticks"
194+
stop 1
195+
end if
196+
197+
! Test only positive log region
198+
call compute_scale_ticks('symlog', 10.0_wp, 1000.0_wp, threshold, tick_positions, num_ticks)
199+
200+
if (num_ticks < 1) then
201+
print *, "FAIL: symlog positive-log-only should generate ticks"
202+
stop 1
203+
end if
204+
205+
! All ticks should be positive and > threshold
206+
if (any(tick_positions(1:num_ticks) <= threshold)) then
207+
print *, "FAIL: symlog positive-log-only should only have positive log ticks"
208+
stop 1
209+
end if
210+
211+
! Test only negative log region
212+
call compute_scale_ticks('symlog', -1000.0_wp, -10.0_wp, threshold, tick_positions, num_ticks)
213+
214+
if (num_ticks < 1) then
215+
print *, "FAIL: symlog negative-log-only should generate ticks"
216+
stop 1
217+
end if
218+
219+
! All ticks should be negative and < -threshold
220+
if (any(tick_positions(1:num_ticks) >= -threshold)) then
221+
print *, "FAIL: symlog negative-log-only should only have negative log ticks"
222+
stop 1
223+
end if
224+
end subroutine test_symlog_single_region_cases
225+
226+
end program test_symlog_axes_implementation

0 commit comments

Comments
 (0)