adjust Fortran API

This commit is contained in:
Gregor Weiss 2024-10-09 21:20:00 +02:00
parent 06b96ae5af
commit d8e2e58862
Signed by: Gregor Weiss
GPG key ID: 61E170A8BBFE5756

View file

@ -48,10 +48,10 @@ module bwc
!| | | \| |___ |___ |__| |__/ |___ |! !| | | \| |___ |___ |__| |__/ |___ |!
!| |! !| |!
!************************************************************************************************! !************************************************************************************************!
use, intrinsic :: iso_c_binding, only: C_PTR, C_INT64_T, C_INT32_T, C_INT16_T, C_INT8_T, & use, intrinsic :: iso_c_binding, only: c_ptr, c_int64_t, c_int32_t, c_int16_t, c_int8_t, &
C_INT, C_DOUBLE, C_CHAR, C_SIGNED_CHAR c_int, c_double, c_char, c_signed_char
IMPLICIT NONE implicit none
PRIVATE private
!************************************************************************************************! !************************************************************************************************!
!| ____ ____ _ _ ____ ___ ____ _ _ ___ ____ |! !| ____ ____ _ _ ____ ___ ____ _ _ ___ ____ |!
@ -59,25 +59,25 @@ module bwc
!| |___ |__| | \| ___] | | | | \| | ___] |! !| |___ |__| | \| ___] | | | | \| | ___] |!
!| |! !| |!
!************************************************************************************************! !************************************************************************************************!
ENUM, BIND(C) enum, bind(c)
enumerator :: bwc_dwt_9_7 = 0, & enumerator :: bwc_dwt_9_7 = 0, &
bwc_dwt_5_3 = 1, & bwc_dwt_5_3 = 1, &
bwc_dwt_haar = 2 bwc_dwt_haar = 2
END ENUM end enum
!*==============================================================================================*! !*==============================================================================================*!
ENUM, BIND(C) enum, bind(c)
enumerator :: bwc_prog_LRCP = 0 enumerator :: bwc_prog_lrcp = 0
END ENUM end enum
!*==============================================================================================*! !*==============================================================================================*!
ENUM, BIND(C) enum, bind(c)
enumerator :: bwc_qt_none = 0, & enumerator :: bwc_qt_none = 0, &
bwc_qt_derived = 1 bwc_qt_derived = 1
END ENUM end enum
!*==============================================================================================*! !*==============================================================================================*!
ENUM, BIND(C) enum, bind(c)
enumerator :: bwc_tile_sizeof = 0, & enumerator :: bwc_tile_sizeof = 0, &
bwc_tile_numbof = 1 bwc_tile_numbof = 1
END ENUM end enum
!************************************************************************************************! !************************************************************************************************!
!| ___ _ _ ___ _ _ ____ ____ _ _ _ _ ____ ___ _ ____ _ _ ____ |! !| ___ _ _ ___ _ _ ____ ____ _ _ _ _ ____ ___ _ ____ _ _ ____ |!
@ -86,258 +86,113 @@ module bwc
!| |! !| |!
!************************************************************************************************! !************************************************************************************************!
interface interface
function initialize_data_f(field, nX, nY, nZ, nTS, nPar, file_extension) result(data) & function init_stream_f(inpbuf, outbuf, mode) result(stream) &
BIND(C, NAME="bwc_initialize_data") bind(c, name="bwc_init_stream")
IMPORT import
!*-----------------------*! type(c_ptr) :: stream
! DEFINE POINTERS: ! type(c_ptr), value :: inpbuf
!*-----------------------*! type(c_ptr), value :: outbuf
TYPE(C_PTR), VALUE :: field integer(kind=c_int), value :: mode
TYPE(C_PTR) :: data end function init_stream_f
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT16_T), VALUE :: nX, nY, nZ
INTEGER(KIND=C_INT8_T), VALUE :: nTS, nPar
!*-----------------------*!
! DEFINE CHAR VARIABLES: !
!*-----------------------*!
CHARACTER(KIND=C_CHAR) :: file_extension(*)
end function initialize_data_f
!*============================================================================================*! !*============================================================================================*!
subroutine free_data_f(data) & function alloc_coder_f(nx, ny, nz, nts, npar, prec) result(codec) &
BIND(C, NAME="bwc_free_data") bind(c, name="bwc_alloc_coder")
IMPORT import
!*-----------------------*! type(c_ptr) :: codec
! DEFINE POINTERS: ! integer(kind=c_int64_t), value :: nx, ny, nz, nts
!*-----------------------*! integer(kind=c_int8_t), value :: npar
TYPE(C_PTR), VALUE :: data integer(kind=c_int), value :: prec
end subroutine free_data_f end function alloc_coder_f
!*============================================================================================*! !*============================================================================================*!
subroutine kill_compression_f(field) & function alloc_decoder_f() result(codec) &
BIND(C, NAME="bwc_kill_compression") bind(c, name="bwc_alloc_decoder")
IMPORT import
!*-----------------------*! type(c_ptr) :: codec
! DEFINE POINTERS: ! end function alloc_decoder_f
!*-----------------------*!
TYPE(C_PTR), VALUE :: field
end subroutine kill_compression_f
!*============================================================================================*! !*============================================================================================*!
function initialize_field_f(data) result(field) & subroutine free_codec_f(codec) &
BIND(C, NAME="bwc_initialize_field") bind(c, name="bwc_free_codec")
IMPORT import
!*-----------------------*! type(c_ptr), value :: codec
! DEFINE POINTERS: ! end subroutine free_codec_f
!*-----------------------*!
TYPE(C_PTR), VALUE :: data
TYPE(C_PTR) :: field
end function initialize_field_f
!*============================================================================================*! !*============================================================================================*!
subroutine set_error_resilience_f(field) & subroutine set_error_resilience_f(codec) &
BIND(C, NAME="bwc_set_error_resilience") bind(c, name="bwc_set_error_resilience")
IMPORT import
!*-----------------------*! type(c_ptr), value :: codec
! DEFINE POINTERS: !
!*-----------------------*!
TYPE(C_PTR), VALUE :: field
end subroutine set_error_resilience_f end subroutine set_error_resilience_f
!*============================================================================================*! !*============================================================================================*!
subroutine set_quantization_style_f(field, quantization_style) & subroutine set_decomp_f(codec, decompx, decompy, decompz, decompts) &
BIND(C, NAME="bwc_set_quantization_style") bind(c, name="bwc_set_decomp")
IMPORT import
!*-----------------------*! type(c_ptr), value :: codec
! DEFINE POINTERS: ! integer(kind=c_int8_t), value :: decompx, decompy
!*-----------------------*! integer(kind=c_int8_t), value :: decompz, decompts
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT), VALUE :: quantization_style
end subroutine set_quantization_style_f
!*============================================================================================*!
subroutine set_quantization_step_size_f(field, delta) &
BIND(C, NAME="bwc_set_quantization_step_size")
IMPORT
!*-----------------------*!
! DEFINE POINTERS: !
!*-----------------------*!
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE FLOAT VARIABLES: !
!*-----------------------*!
REAL(KIND=C_DOUBLE), VALUE :: delta
end subroutine set_quantization_step_size_f
!*============================================================================================*!
subroutine set_progression_f(field, progression) &
BIND(C, NAME="bwc_set_progression")
IMPORT
!*-----------------------*!
! DEFINE POINTERS: !
!*-----------------------*!
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT), VALUE :: progression
end subroutine set_progression_f
!*============================================================================================*!
subroutine set_kernels_f(field, KernelX, KernelY, KernelZ, KernelTS) &
BIND(C, NAME="bwc_set_kernels")
IMPORT
!*-----------------------*!
! DEFINE POINTERS: !
!*-----------------------*!
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT), VALUE :: KernelX, KernelY
INTEGER(KIND=C_INT), VALUE :: KernelZ, KernelTS
end subroutine set_kernels_f
!*============================================================================================*!
subroutine set_decomp_f(field, decompX, decompY, decompZ, decompTS) &
BIND(C, NAME="bwc_set_decomp")
IMPORT
!*-----------------------*!
! DEFINE POINTERS: !
!*-----------------------*!
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T), VALUE :: decompX, decompY
INTEGER(KIND=C_INT8_T), VALUE :: decompZ, decompTS
end subroutine set_decomp_f end subroutine set_decomp_f
!*============================================================================================*! !*============================================================================================*!
subroutine set_precincts_f(field, pX, pY, pZ, pTS) & subroutine set_precincts_f(codec, px, py, pz, pts) &
BIND(C, NAME="bwc_set_precincts") bind(c, name="bwc_set_precincts")
IMPORT import
!*-----------------------*! type(c_ptr), value :: codec
! DEFINE POINTERS: ! integer(kind=c_int8_t), value :: px, py
!*-----------------------*! integer(kind=c_int8_t), value :: pz, pts
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T), VALUE :: pX, pY
INTEGER(KIND=C_INT8_T), VALUE :: pZ, pTS
end subroutine set_precincts_f end subroutine set_precincts_f
!*============================================================================================*! !*============================================================================================*!
subroutine set_codeblocks_f(field, cbX, cbY, cbZ, cbTS) & subroutine set_codeblocks_f(codec, cbx, cby, cbz, cbts) &
BIND(C, NAME="bwc_set_codeblocks") bind(c, name="bwc_set_codeblocks")
IMPORT import
!*-----------------------*! type(c_ptr), value :: codec
! DEFINE POINTERS: ! integer(kind=c_int8_t), value :: cbx, cby
!*-----------------------*! integer(kind=c_int8_t), value :: cbz, cbts
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T), VALUE :: cbX, cbY
INTEGER(KIND=C_INT8_T), VALUE :: cbZ, cbTS
end subroutine set_codeblocks_f end subroutine set_codeblocks_f
!*============================================================================================*! !*============================================================================================*!
subroutine set_qm_f(field, Qm) & subroutine set_qm_f(codec, qm) &
BIND(C, NAME="bwc_set_qm") bind(c, name="bwc_set_qm")
IMPORT import
!*-----------------------*! type(c_ptr), value :: codec
! DEFINE POINTERS: ! integer(kind=c_int8_t), value :: qm
!*-----------------------*!
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T), VALUE :: Qm
end subroutine set_qm_f end subroutine set_qm_f
!*============================================================================================*! !*============================================================================================*!
subroutine set_tiles_f(field, tilesX, tilesY, tilesZ, tilesTS, instr) & subroutine set_tiles_f(codec, tilesx, tilesy, tilesz, tilests, instr) &
BIND(C, NAME="bwc_set_tiles") bind(c, name="bwc_set_tiles")
IMPORT import
!*-----------------------*! type(c_ptr), value :: codec
! DEFINE POINTERS: ! integer(kind=c_int64_t), value :: tilesx, tilesy, tilesz, tilests
!*-----------------------*! integer(kind=c_int), value :: instr
TYPE(C_PTR), VALUE :: field
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT64_T), VALUE :: tilesX, tilesY, tilesZ
INTEGER(KIND=C_INT16_T), VALUE :: tilesTS
INTEGER(KIND=C_INT), VALUE :: instr
end subroutine set_tiles_f end subroutine set_tiles_f
!*============================================================================================*! !*============================================================================================*!
function create_compression_f(field, rate_control) result(error_flag) & function create_compression_f(codec, stream, rate_control) result(error_flag) &
BIND(C, NAME="bwc_create_compression") bind(c, name="bwc_create_compression")
IMPORT import
!*-----------------------*! integer(kind=c_int8_t) :: error_flag
! DEFINE POINTERS: ! type(c_ptr), value :: codec
!*-----------------------*! type(c_ptr), value :: stream
TYPE(C_PTR), VALUE :: field character(kind=c_char) :: rate_control(*)
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T) :: error_flag
!*-----------------------*!
! DEFINE CHAR VARIABLES: !
!*-----------------------*!
CHARACTER(KIND=C_CHAR) :: rate_control(*)
end function create_compression_f end function create_compression_f
!*============================================================================================*! !*============================================================================================*!
function compress_f(field, data) result(error_flag) & function compress_f(codec, stream) result(error_flag) &
BIND(C, NAME="bwc_compress") bind(c, name="bwc_compress")
IMPORT import
!*-----------------------*! integer(kind=c_int8_t) :: error_flag
! DEFINE POINTERS: ! type(c_ptr), value :: codec
!*-----------------------*! type(c_ptr), value :: stream
TYPE(C_PTR), VALUE :: field
TYPE(C_PTR), VALUE :: data
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T) :: error_flag
end function compress_f end function compress_f
!*============================================================================================*! !*============================================================================================*!
function create_decompression_f(data, layer) result(field) & function create_decompression_f(codec, stream, layer) result(error_flag) &
BIND(C, NAME="bwc_create_decompression") bind(c, name="bwc_create_decompression")
IMPORT import
!*-----------------------*! integer(kind=c_int8_t) :: error_flag
! DEFINE POINTERS: ! type(c_ptr), value :: codec
!*-----------------------*! type(c_ptr), value :: stream
TYPE(C_PTR) :: field integer(kind=c_int8_t), value :: layer
TYPE(C_PTR), VALUE :: data
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T), VALUE :: layer
end function create_decompression_f end function create_decompression_f
!*============================================================================================*! !*============================================================================================*!
function decompress_f(field, data) result(error_flag) & function decompress_f(codec, stream) result(error_flag) &
BIND(C, NAME="bwc_decompress") bind(c, name="bwc_decompress")
IMPORT import
!*-----------------------*! integer(kind=c_int8_t) :: error_flag
! DEFINE POINTERS: ! type(c_ptr), value :: codec
!*-----------------------*! type(c_ptr), value :: stream
TYPE(C_PTR), VALUE :: field
TYPE(C_PTR), VALUE :: data
!*-----------------------*!
! DEFINE INT VARIABLES: !
!*-----------------------*!
INTEGER(KIND=C_INT8_T) :: error_flag
end function decompress_f end function decompress_f
end interface end interface
@ -359,22 +214,17 @@ module bwc
public :: bwc_tile_sizeof, & public :: bwc_tile_sizeof, &
bwc_tile_numbof bwc_tile_numbof
public :: bwc_initialize_data, & public :: bwc_init_stream, &
bwc_free_data bwc_alloc_coder, &
bwc_alloc_decoder, &
public :: bwc_initialize_field, & bwc_free_codec
bwc_kill_compression
public :: bwc_set_error_resilience, & public :: bwc_set_error_resilience, &
bwc_set_quantization_style, &
bwc_set_quantization_step_size, &
bwc_set_progression, &
bwc_set_kernels, &
bwc_set_decomp, & bwc_set_decomp, &
bwc_set_precincts, & bwc_set_precincts, &
bwc_set_codeblocks, & bwc_set_codeblocks, &
bwc_set_qm, & bwc_set_qm, &
bwc_set_tiles, bwc_set_tiles
public :: bwc_create_compression, & public :: bwc_create_compression, &
bwc_compress, & bwc_compress, &