Skip to content

Commit ec82037

Browse files
authored
Fix SIGBUS when saving PNG on Apple Silicon (#1410)
### **User description** ## Summary - add zlib_compress_into subroutine to avoid returning large allocatables from functions - keep existing zlib_compress function as wrapper for backwards compatibility - update raster/pdf backends to call the new helper and add optional debug logging ## Testing - fpm test ___ ### **PR Type** Bug fix, Enhancement ___ ### **Description** - Add `zlib_compress_into` subroutine to avoid returning large allocatables - Keep existing `zlib_compress` function as backwards-compatible wrapper - Update PNG and PDF backends to use new helper - Add optional debug logging with environment variable control ___ ### Diagram Walkthrough ```mermaid flowchart LR A["zlib_compress function"] --> B["zlib_compress_into subroutine"] B --> C["PNG backend"] B --> D["PDF backend"] B --> E["Debug logging"] A --> F["Backwards compatibility wrapper"] ``` <details> <summary><h3> File Walkthrough</h3></summary> <table><thead><tr><th></th><th align="left">Relevant files</th></tr></thead><tbody><tr><td><strong>Enhancement</strong></td><td><table> <tr> <td> <details> <summary><strong>fortplot_zlib_core.f90</strong><dd><code>Add safer compression subroutine with debug logging</code>&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; </dd></summary> <hr> src/external/fortplot_zlib_core.f90 <ul><li>Add <code>zlib_compress_into</code> subroutine that allocates output buffer <br>directly<br> <li> Convert existing <code>zlib_compress</code> to wrapper calling new subroutine<br> <li> Add debug logging infrastructure with environment variable control<br> <li> Add utility functions for environment parsing and case conversion</ul> </details> </td> <td><a href="https://github.com/lazy-fortran/fortplot/pull/1410/files#diff-a88e04b74f6df05653fd8293cdb98c45343981c51bc782a5a54d2ee55e871444">+117/-24</a></td> </tr> <tr> <td> <details> <summary><strong>fortplot_zlib.f90</strong><dd><code>Export new compression subroutine in bridge module</code>&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; </dd></summary> <hr> src/external/fortplot_zlib.f90 <ul><li>Add <code>zlib_compress_into</code> to module exports<br> <li> Update public interface to include both old and new compression <br>functions</ul> </details> </td> <td><a href="https://github.com/lazy-fortran/fortplot/pull/1410/files#diff-11e72eef971d431a23ca9c3637c35fd311a7856f1016b8b55c0ad0af3a12bd0d">+3/-3</a>&nbsp; &nbsp; &nbsp; </td> </tr> </table></td></tr><tr><td><strong>Bug fix</strong></td><td><table> <tr> <td> <details> <summary><strong>fortplot_png.f90</strong><dd><code>Update PNG backend to use new compression subroutine</code>&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; </dd></summary> <hr> src/backends/raster/fortplot_png.f90 <ul><li>Update import to use <code>zlib_compress_into</code> instead of <code>zlib_compress</code><br> <li> Replace function call with subroutine call in <code>generate_png_data</code></ul> </details> </td> <td><a href="https://github.com/lazy-fortran/fortplot/pull/1410/files#diff-82ad17eefff2c68aa18f549db7efad68da2811533f2fc213343875f2293d6605">+2/-2</a>&nbsp; &nbsp; &nbsp; </td> </tr> <tr> <td> <details> <summary><strong>fortplot_pdf.f90</strong><dd><code>Update PDF backend to use new compression subroutine</code>&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; </dd></summary> <hr> src/backends/vector/fortplot_pdf.f90 <ul><li>Update import to use <code>zlib_compress_into</code> instead of <code>zlib_compress</code><br> <li> Replace function call with subroutine call in heatmap wrapper</ul> </details> </td> <td><a href="https://github.com/lazy-fortran/fortplot/pull/1410/files#diff-b6808bf1e748bba7bf8e9d2e3508fbc62435a6cbc3eec4b2354c3f31bc319e2a">+2/-2</a>&nbsp; &nbsp; &nbsp; </td> </tr> <tr> <td> <details> <summary><strong>fortplot_pdf_io.f90</strong><dd><code>Update PDF I/O to use new compression subroutine</code>&nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; &nbsp; </dd></summary> <hr> src/backends/vector/fortplot_pdf_io.f90 <ul><li>Update import to use <code>zlib_compress_into</code> instead of <code>zlib_compress</code><br> <li> Replace function call with subroutine call in <code>write_content_object</code></ul> </details> </td> <td><a href="https://github.com/lazy-fortran/fortplot/pull/1410/files#diff-c9accba28af59737231fe1bc2218677eb9f7840fc05186d18a72623e8bf8cb6d">+2/-2</a>&nbsp; &nbsp; &nbsp; </td> </tr> </table></td></tr></tr></tbody></table> </details> ___
1 parent 0c63027 commit ec82037

File tree

5 files changed

+71
-33
lines changed

5 files changed

+71
-33
lines changed

src/backends/raster/fortplot_png.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module fortplot_png
22
use iso_c_binding
33
use fortplot_context, only: setup_canvas
44
use fortplot_raster, only: raster_context, create_raster_canvas, raster_draw_axes_and_labels, raster_render_ylabel
5-
use fortplot_zlib_core, only: zlib_compress, crc32_calculate
5+
use fortplot_zlib_core, only: zlib_compress_into, crc32_calculate
66
use fortplot_logging, only: log_error, log_info
77
use, intrinsic :: iso_fortran_env, only: wp => real64, int8, int32
88
implicit none
@@ -104,7 +104,7 @@ subroutine generate_png_data(width, height, image_data, png_buffer)
104104
call convert_rgb_to_png_rows(width, height, image_data, png_row_data)
105105

106106
data_size = size(png_row_data)
107-
compressed_data = zlib_compress(png_row_data, data_size, compressed_size)
107+
call zlib_compress_into(png_row_data, data_size, compressed_data, compressed_size)
108108

109109
if (.not. allocated(compressed_data) .or. compressed_size <= 0) then
110110
call log_error("PNG compression failed")

src/backends/vector/fortplot_pdf.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ module fortplot_pdf
44
use fortplot_pdf_core
55
use fortplot_pdf_text
66
use fortplot_pdf_drawing
7-
use fortplot_zlib_core, only: zlib_compress
7+
use fortplot_zlib_core, only: zlib_compress_into
88
use fortplot_pdf_axes, only: draw_pdf_axes_and_labels, render_mixed_text
99
use fortplot_pdf_io
1010
use fortplot_pdf_coordinate
@@ -396,7 +396,7 @@ subroutine fill_heatmap_wrapper(this, x_grid, y_grid, z_grid, z_min, z_max)
396396
do k = 1, n
397397
in_bytes(k) = int(iand(rgb_u8(k),255))
398398
end do
399-
out_bytes = zlib_compress(in_bytes, n, out_len)
399+
call zlib_compress_into(in_bytes, n, out_bytes, out_len)
400400
img_data = repeat(' ', out_len)
401401
do k = 1, out_len
402402
img_data(k:k) = achar(iand(int(out_bytes(k), kind=4), 255))

src/backends/vector/fortplot_pdf_io.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module fortplot_pdf_io
55
use iso_fortran_env, only: wp => real64
66
use fortplot_pdf_core, only: pdf_context_core
77
use, intrinsic :: iso_fortran_env, only: int8
8-
use fortplot_zlib_core, only: zlib_compress
8+
use fortplot_zlib_core, only: zlib_compress_into
99
use fortplot_logging, only: log_error
1010
implicit none
1111
private
@@ -263,7 +263,7 @@ subroutine write_content_object(unit, ctx, pos)
263263
do i = 1, stream_len
264264
in_bytes(i) = int(iachar(ctx%stream_data(i:i)), int8)
265265
end do
266-
out_bytes = zlib_compress(in_bytes, stream_len, out_len)
266+
call zlib_compress_into(in_bytes, stream_len, out_bytes, out_len)
267267
! Build a character buffer from compressed bytes
268268
n = out_len
269269
compressed_str = repeat(' ', n)

src/external/fortplot_zlib.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,10 @@
11
module fortplot_zlib_bridge
22
!! Bridge module to re-export from the main fortplot_zlib_core
33
!! This maintains compatibility while using the working full implementation
4-
use fortplot_zlib_core, only: zlib_compress, crc32_calculate
4+
use fortplot_zlib_core, only: zlib_compress, zlib_compress_into, crc32_calculate
55
implicit none
66

77
private
8-
public :: zlib_compress, crc32_calculate
8+
public :: zlib_compress, zlib_compress_into, crc32_calculate
99

10-
end module fortplot_zlib_bridge
10+
end module fortplot_zlib_bridge

src/external/fortplot_zlib_core.f90

Lines changed: 62 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -3,13 +3,18 @@ module fortplot_zlib_core
33
!! Ported from STB image libraries for self-contained PNG support
44
use, intrinsic :: iso_fortran_env, only: int8, int32
55
use iso_c_binding, only: c_ptr, c_loc, c_f_pointer, c_associated
6+
use fortplot_logging, only: log_debug, set_log_level, LOG_LEVEL_DEBUG
7+
use fortplot_string_utils, only: parse_boolean_env
68
implicit none
79

810
private
9-
public :: zlib_compress, zlib_decompress, crc32_calculate
10-
11+
public :: zlib_compress, zlib_compress_into, zlib_decompress, crc32_calculate
12+
public :: initialize_zlib_debug
13+
1114
private :: bit_reverse
1215

16+
logical, save :: zlib_debug_initialized = .false.
17+
1318
! Deflate compression constants
1419
integer, parameter :: MAX_MATCH = 258
1520
integer, parameter :: MIN_MATCH = 3
@@ -42,6 +47,7 @@ module fortplot_zlib_core
4247
7, 7, 8, 8, 9, 9, 10, 10, &
4348
11, 11, 12, 12, 13, 13 ]
4449

50+
4551
! CRC32 lookup table (standard polynomial 0xEDB88320)
4652
integer(int32), parameter :: crc_table(0:255) = [ &
4753
int(z'00000000',int32), int(z'77073096',int32), int(z'EE0E612C',int32), int(z'990951BA',int32), &
@@ -129,50 +135,81 @@ function crc32_calculate(data, data_len) result(crc)
129135
crc = not(crc) ! Final XOR with 0xFFFFFFFF
130136
end function crc32_calculate
131137

132-
function zlib_compress(input_data, input_len, output_len) result(output_data)
133-
!! Full deflate compression with LZ77 and Huffman coding
138+
subroutine initialize_zlib_debug()
139+
!! Initialize debug logging based on FORTPLOT_ZLIB_DEBUG environment variable
140+
character(len=32) :: env_value
141+
integer :: status
142+
143+
if (zlib_debug_initialized) return
144+
145+
call get_environment_variable('FORTPLOT_ZLIB_DEBUG', env_value, status=status)
146+
if (status == 0 .and. len_trim(env_value) > 0) then
147+
if (parse_boolean_env(env_value)) then
148+
call set_log_level(LOG_LEVEL_DEBUG)
149+
end if
150+
end if
151+
zlib_debug_initialized = .true.
152+
end subroutine initialize_zlib_debug
153+
154+
subroutine zlib_compress_into(input_data, input_len, output_data, output_len)
155+
!! Compress data into a newly allocated buffer
134156
integer(int8), intent(in) :: input_data(*)
135157
integer, intent(in) :: input_len
158+
integer(int8), allocatable, intent(out) :: output_data(:)
136159
integer, intent(out) :: output_len
137-
integer(int8), allocatable :: output_data(:)
138-
160+
139161
integer(int8), allocatable :: compressed_block(:)
140162
integer :: compressed_block_len
141163
integer(int32) :: adler32_checksum
142164
integer :: pos
143-
144-
! Compress using deflate algorithm
165+
character(len=160) :: debug_message
166+
167+
call initialize_zlib_debug()
168+
169+
write(debug_message, '(a,i0)') '[fortplot:zlib] compress_into begin, input_len=', input_len
170+
call log_debug(debug_message)
171+
145172
call deflate_compress(input_data, input_len, compressed_block, compressed_block_len)
146-
147-
! Calculate total output size: zlib header (2) + compressed data + adler32 (4)
173+
174+
write(debug_message, '(a,i0)') '[fortplot:zlib] deflate returned compressed_block_len=', &
175+
compressed_block_len
176+
call log_debug(debug_message)
177+
148178
output_len = 2 + compressed_block_len + 4
149179
allocate(output_data(output_len))
150-
180+
151181
pos = 1
152-
153-
! Write zlib header
154-
output_data(pos) = int(z'78', int8) ! CMF: 32K window, deflate
182+
output_data(pos) = int(z'78', int8)
155183
pos = pos + 1
156-
output_data(pos) = int(z'5E', int8) ! FLG: no preset dict, level 1 compression
184+
output_data(pos) = int(z'5E', int8)
157185
pos = pos + 1
158-
159-
! Copy compressed block
160-
output_data(pos:pos+compressed_block_len-1) = compressed_block(1:compressed_block_len)
186+
output_data(pos:pos + compressed_block_len - 1) = &
187+
compressed_block(1:compressed_block_len)
161188
pos = pos + compressed_block_len
162-
163-
! Calculate and write Adler-32 checksum
189+
164190
adler32_checksum = calculate_adler32(input_data, input_len)
165-
166-
! Write Adler-32 in big-endian format
167191
output_data(pos) = int(iand(ishft(adler32_checksum, -24), 255), int8)
168192
pos = pos + 1
169193
output_data(pos) = int(iand(ishft(adler32_checksum, -16), 255), int8)
170194
pos = pos + 1
171195
output_data(pos) = int(iand(ishft(adler32_checksum, -8), 255), int8)
172196
pos = pos + 1
173197
output_data(pos) = int(iand(adler32_checksum, 255), int8)
174-
198+
175199
deallocate(compressed_block)
200+
201+
write(debug_message, '(a,i0)') '[fortplot:zlib] total output_len=', output_len
202+
call log_debug(debug_message)
203+
end subroutine zlib_compress_into
204+
205+
function zlib_compress(input_data, input_len, output_len) result(output_data)
206+
!! Backwards-compatible wrapper returning an allocatable result
207+
integer(int8), intent(in) :: input_data(*)
208+
integer, intent(in) :: input_len
209+
integer, intent(out) :: output_len
210+
integer(int8), allocatable :: output_data(:)
211+
212+
call zlib_compress_into(input_data, input_len, output_data, output_len)
176213
end function zlib_compress
177214

178215
function zlib_decompress(input_data, input_len, status, verify_checksum) result(output_data)
@@ -949,7 +986,7 @@ function bit_reverse(value, num_bits) result(reversed_value)
949986
integer, intent(in) :: value, num_bits
950987
integer :: reversed_value
951988
integer :: i
952-
989+
953990
reversed_value = 0
954991
do i = 0, num_bits - 1
955992
if (iand(ishft(value, -i), 1) == 1) then
@@ -958,4 +995,5 @@ function bit_reverse(value, num_bits) result(reversed_value)
958995
end do
959996
end function bit_reverse
960997

998+
961999
end module fortplot_zlib_core

0 commit comments

Comments
 (0)