37 integer,
allocatable,
target,
save :: isc_f(:), link_f(:), itp_f(:), jmpb_f(:), irf_f(:)
38 character(len=10),
allocatable,
target,
save :: tag_f(:)
39 character(len=3),
allocatable,
target,
save :: typ_f(:)
53 function c_f_string(c_str)
result(f_str)
54 character(kind=c_char,len=1),
intent(in) :: c_str(*)
55 character(len=:),
allocatable :: f_str
59 do while (c_str(nchars) /= c_null_char)
64 allocate(
character(len=nchars) :: f_str)
65 f_str = transfer(c_str(1:nchars), f_str)
66 end function c_f_string
75 subroutine copy_f_c_str(f_str, c_str, c_str_len)
76 character(len=*),
target,
intent(in) :: f_str
77 character(kind=c_char, len=1),
intent(inout) :: c_str(*)
78 integer,
intent(in) :: c_str_len
79 integer :: max_str_len
81 if (c_str_len /= 0)
then
82 max_str_len = c_str_len
83 c_str(1)(1:max_str_len) = f_str(1:max_str_len)
84 c_str(1)(max_str_len:max_str_len) = c_null_char
86 end subroutine copy_f_c_str
94 subroutine open_c(lunit, filepath) bind(C, name='open_f')
95 integer(c_int),
value,
intent(in) :: lunit
96 character(kind=c_char, len=1) :: filepath
98 open(lunit, file=c_f_string(filepath))
106 subroutine close_c(lunit) bind(C, name='close_f')
107 integer(c_int),
value,
intent(in) :: lunit
122 subroutine openbf_c(bufr_unit, cio, table_file_id) bind(C, name='openbf_f')
123 integer(c_int),
value,
intent(in) :: bufr_unit
124 character(kind=c_char, len=1),
intent(in) :: cio(*)
125 integer(c_int),
value,
intent(in) :: table_file_id
127 call openbf(bufr_unit, c_f_string(cio), table_file_id)
137 subroutine closbf_c(bufr_unit) bind(C, name='closbf_f')
138 integer(c_int),
value,
intent(in) :: bufr_unit
166 function ireadmg_c(bufr_unit, c_subset, iddate, subset_str_len)
result(ires) bind(C, name='ireadmg_f')
167 integer(c_int),
value,
intent(in) :: bufr_unit
168 character(kind=c_char, len=1),
intent(out) :: c_subset(*)
169 integer(c_int),
intent(out) :: iddate
170 integer(c_int),
value,
intent(in) :: subset_str_len
171 integer(c_int) :: ires
172 character(len=25) :: f_subset
175 ires =
ireadmg(bufr_unit, f_subset, iddate)
178 call copy_f_c_str(f_subset, c_subset, int(subset_str_len))
192 function ireadsb_c(bufr_unit)
result(ires) bind(C, name='ireadsb_f')
193 integer(c_int),
value,
intent(in) :: bufr_unit
194 integer(c_int) :: ires
211 subroutine ufbint_c(bufr_unit, c_data, dim_1, dim_2, iret, table_b_mnemonic) bind(C, name='ufbint_f')
212 integer(c_int),
value,
intent(in) :: bufr_unit
213 type(c_ptr),
intent(inout) :: c_data
214 integer(c_int),
value,
intent(in) :: dim_1, dim_2
215 integer(c_int),
intent(out) :: iret
216 character(kind=c_char, len=1),
intent(in) :: table_b_mnemonic(*)
217 real,
pointer :: f_data
219 call c_f_pointer(c_data, f_data)
220 call ufbint(bufr_unit, f_data, dim_1, dim_2, iret, c_f_string(table_b_mnemonic))
234 subroutine ufbrep_c(bufr_unit, c_data, dim_1, dim_2, iret, table_b_mnemonic) bind(C, name='ufbrep_f')
235 integer(c_int),
value,
intent(in) :: bufr_unit
236 type(c_ptr),
intent(inout) :: c_data
237 integer(c_int),
value,
intent(in) :: dim_1, dim_2
238 integer(c_int),
intent(out) :: iret
239 character(kind=c_char, len=1),
intent(in) :: table_b_mnemonic(*)
240 real,
pointer :: f_data
242 call c_f_pointer(c_data, f_data)
243 call ufbrep(bufr_unit, f_data, dim_1, dim_2, iret, c_f_string(table_b_mnemonic))
255 subroutine mtinfo_c(path, file_unit_1, file_unit_2) bind(C, name='mtinfo_f')
256 character(kind=c_char, len=1),
intent(in) :: path(*)
257 integer(c_int),
value,
intent(in) :: file_unit_1
258 integer(c_int),
value,
intent(in) :: file_unit_2
260 call mtinfo(c_f_string(path), file_unit_1, file_unit_2)
273 subroutine status_c(file_unit, lun, il, im) bind(C, name='status_f')
274 integer(c_int),
value,
intent(in) :: file_unit
275 integer(c_int),
intent(out) :: lun
276 integer(c_int),
intent(out) :: il
277 integer(c_int),
intent(out) :: im
279 call status(file_unit, lun, il, im)
295 subroutine nemdefs_c(file_unit, mnemonic, unit_c, unit_str_len, desc_c, desc_str_len, iret) &
296 bind(c, name=
'nemdefs_f')
297 integer(c_int),
value,
intent(in) :: file_unit
298 character(kind=c_char,len=1),
intent(in) :: mnemonic(*)
299 character(kind=c_char, len=1),
intent(out) :: unit_c(*)
300 integer(c_int),
value,
intent(in) :: unit_str_len
301 character(kind=c_char, len=1),
intent(out) :: desc_c(*)
302 integer(c_int),
value,
intent(in) :: desc_str_len
303 integer(c_int),
intent(out) :: iret
305 character(len=25) :: unit_f
306 character(len=55) :: desc_f
309 call nemdefs ( file_unit, c_f_string(mnemonic), desc_f, unit_f, iret)
313 call copy_f_c_str(unit_f, unit_c, min(len(unit_f), unit_str_len))
315 call copy_f_c_str(desc_f, desc_c, min(len(desc_f), desc_str_len))
333 subroutine nemspecs_c(file_unit, mnemonic, mnemonic_idx, scale, reference, bits, iret) &
334 bind(c, name=
'nemspecs_f')
335 integer(c_int),
value,
intent(in) :: file_unit
336 character(kind=c_char,len=1),
intent(in) :: mnemonic(*)
337 integer(c_int),
value,
intent(in) ::mnemonic_idx
338 integer(c_int),
intent(out) :: scale
339 integer(c_int),
intent(out) :: reference
340 integer(c_int),
intent(out) :: bits
341 integer(c_int),
intent(out) :: iret
344 call nemspecs(file_unit, c_f_string(mnemonic), mnemonic_idx, scale, reference, bits, iret)
358 subroutine nemtab_c(lun, mnemonic, descriptor, table_type, table_idx) &
359 bind(c, name=
'nemtab_f')
360 integer(c_int),
value,
intent(in) :: lun
361 character(kind=c_char,len=1),
intent(in) :: mnemonic(*)
362 integer(c_int),
intent(out) :: descriptor
363 character(kind=c_char,len=1),
intent(out) :: table_type(*)
364 integer(c_int),
intent(out) :: table_idx
366 character(len=1) :: table_type_f
368 call nemtab(lun, c_f_string(mnemonic), descriptor, table_type_f, table_idx)
370 table_type(1)(1:1) = table_type_f(1:1)
386 subroutine nemtbb_c(lun, table_idx, unit_str, unit_str_len, scale, reference, bits) &
387 bind(c, name=
'nemtbb_f')
388 integer(c_int),
intent(in),
value :: lun
389 integer(c_int),
intent(in),
value :: table_idx
390 character(kind=c_char,len=1),
intent(out) :: unit_str(*)
391 integer(c_int),
intent(in),
value :: unit_str_len
392 integer(c_int),
intent(out) :: scale
393 integer(c_int),
intent(out) :: reference
394 integer(c_int),
intent(out) :: bits
396 character(len=25) :: unit_str_f
399 call nemtbb( lun, table_idx, unit_str_f, scale, reference, bits)
400 call copy_f_c_str(unit_str_f, unit_str, min(len(unit_str_f), unit_str_len))
409 subroutine get_isc_c(isc_ptr, isc_size) bind(C, name='get_isc_f')
411 type(c_ptr),
intent(inout) :: isc_ptr
412 integer(c_int),
intent(out) :: isc_size
414 allocate(isc_f(
ntab))
416 isc_size =
size(isc_f)
417 isc_ptr = c_loc(isc_f(1))
426 subroutine get_link_c(link_ptr, link_size) bind(C, name='get_link_f')
428 type(c_ptr),
intent(inout) :: link_ptr
429 integer(c_int),
intent(out) :: link_size
431 allocate(link_f(
ntab))
433 link_size =
size(link_f)
434 link_ptr = c_loc(link_f(1))
443 subroutine get_itp_c(itp_ptr, itp_size) bind(C, name='get_itp_f')
445 type(c_ptr),
intent(inout) :: itp_ptr
446 integer(c_int),
intent(out) :: itp_size
448 allocate(itp_f(
ntab))
450 itp_size =
size(itp_f)
451 itp_ptr = c_loc(itp_f(1))
461 subroutine get_typ_c(typ_ptr, typ_len, mem_size) bind(C, name='get_typ_f')
463 type(c_ptr),
intent(inout) :: typ_ptr
464 integer(c_int),
intent(out) :: typ_len
465 integer(c_int),
intent(out) :: mem_size
467 allocate(typ_f(
ntab))
469 typ_len = len(
typ(1))
470 mem_size =
size(typ_f)
471 typ_ptr = c_loc(typ_f(1))
481 subroutine get_tag_c(tag_ptr, tag_len, mem_size) bind(C, name='get_tag_f')
483 type(c_ptr),
intent(inout) :: tag_ptr
484 integer(c_int),
intent(out) :: tag_len
485 integer(c_int),
intent(out) :: mem_size
487 allocate(tag_f(
ntab))
489 tag_len = len(
tag(1))
490 mem_size =
size(tag_f)
491 tag_ptr = c_loc(tag_f(1))
500 subroutine get_jmpb_c(jmpb_ptr, jmpb_size) bind(C, name='get_jmpb_f')
502 type(c_ptr),
intent(inout) :: jmpb_ptr
503 integer(c_int),
intent(out) :: jmpb_size
505 allocate(jmpb_f(
ntab))
507 jmpb_size =
size(jmpb_f)
508 jmpb_ptr = c_loc(jmpb_f(1))
517 subroutine get_irf_c(irf_ptr, irf_size) bind(C, name='get_irf_f')
519 type(c_ptr),
intent(inout) :: irf_ptr
520 integer(c_int),
intent(out) :: irf_size
522 allocate(irf_f(
ntab))
524 irf_size =
size(irf_f)
525 irf_ptr = c_loc(irf_f(1))
534 subroutine get_inode_c(lun, start_node) bind(C, name='get_inode_f')
536 integer(c_int),
value,
intent(in) :: lun
537 integer(c_int),
intent(out) :: start_node
539 start_node =
inode(lun)
548 subroutine get_nval_c(lun, num_nodes) bind(C, name='get_nval_f')
550 integer(c_int),
value,
intent(in) :: lun
551 integer(c_int),
intent(out) :: num_nodes
553 num_nodes =
nval(lun)
563 subroutine get_val_c(lun, val_ptr, val_size) bind(C, name='get_val_f')
565 integer(c_int),
value,
intent(in) :: lun
566 type(c_ptr),
intent(inout) :: val_ptr
567 integer(c_int),
intent(out) :: val_size
569 val_size =
size(
val(:, lun))
570 val_ptr = c_loc(
val(1, lun))
580 subroutine get_inv_c(lun, inv_ptr, inv_size) bind(C, name='get_inv_f')
582 integer(c_int),
value,
intent(in) :: lun
583 type(c_ptr),
intent(inout) :: inv_ptr
584 integer(c_int),
intent(out) :: inv_size
586 inv_size =
size(
inv(:, lun))
587 inv_ptr = c_loc(
inv(1, lun))
594 if (
allocated(isc_f))
deallocate(isc_f)
595 if (
allocated(link_f))
deallocate(link_f)
596 if (
allocated(itp_f))
deallocate(itp_f)
597 if (
allocated(typ_f))
deallocate(typ_f)
598 if (
allocated(tag_f))
deallocate(tag_f)
599 if (
allocated(jmpb_f))
deallocate(jmpb_f)
600 if (
allocated(irf_f))
deallocate(irf_f)
615 function iupbs01_c(bufr, mnemonic)
result(ires) bind(C, name='iupbs01_f')
616 integer(c_int),
intent(in) :: bufr(*)
617 character(kind=c_char, len=1),
intent(in) :: mnemonic(*)
618 integer(c_int) :: ires
621 ires =
iupbs01(bufr,c_f_string(mnemonic))
634 function igetprm_c(cprmnm)
result(ires) bind(C, name='igetprm_f')
635 character(kind=c_char, len=1),
intent(in) :: cprmnm(*)
636 integer(c_int) :: ires
639 ires =
igetprm(c_f_string(cprmnm))
652 function isetprm_c(cprmnm,ipval)
result(ires) bind(C, name='isetprm_f')
653 character(kind=c_char, len=1),
intent(in) :: cprmnm(*)
654 integer(c_int),
value,
intent(in) :: ipval
655 integer(c_int) :: ires
658 ires =
isetprm(c_f_string(cprmnm),ipval)
670 integer(c_int),
value,
intent(in) :: max0
684 function igetmxby_c()
result(ires) bind(C, name='igetmxby_f')
685 integer(c_int) :: ires
701 subroutine cadn30_c(idn, adn, adn_str_len) bind(C, name='cadn30_f')
702 integer(c_int),
intent(in),
value :: idn, adn_str_len
703 character(kind=c_char, len=1),
intent(out) :: adn(*)
704 character(len=8) :: adn_f
707 call copy_f_c_str(adn_f, adn, adn_str_len)
720 function igetntbi_c(lun, table_type)
result(ires) bind(C, name='igetntbi_f')
721 integer(c_int),
value,
intent(in) :: lun
722 character(kind=c_char,len=1),
intent(in) :: table_type(*)
723 integer(c_int) :: ires
725 character(len=1) :: table_type_f
727 table_type_f(1:1) = table_type(1)(1:1)
741 subroutine elemdx_c(card,lun) bind(C, name='elemdx_f')
742 integer(c_int),
value,
intent(in) :: lun
743 character(kind=c_char, len=1),
intent(in) :: card(*)
744 character(len=80) :: card_f
748 card_f(ii:ii) = card(1)(ii:ii)
765 subroutine numtbd_c(lun,idn,nemo,nemo_str_len,tab,iret) bind(C, name='numtbd_f')
766 integer(c_int),
value,
intent(in) :: lun, idn, nemo_str_len
767 character(kind=c_char,len=1),
intent(out) :: nemo(*), tab(*)
768 integer(c_int),
intent(out) :: iret
770 character(len=9) :: nemo_f
771 character(len=1) :: tab_f
773 call numtbd(lun, idn, nemo_f, tab_f, iret)
775 call copy_f_c_str(nemo_f, nemo, nemo_str_len)
776 tab(1)(1:1) = tab_f(1:1)
789 function ifxy_c(cfxy)
result(ires) bind(C, name='ifxy_f')
790 character(kind=c_char, len=1),
intent(in) :: cfxy(*)
791 integer(c_int) :: ires
794 ires =
ifxy(c_f_string(cfxy))
813 subroutine uptdd_c(id, lun, ient, iret) bind(C, name='uptdd_f')
814 integer(c_int),
intent(in),
value :: id, lun, ient
815 integer(c_int),
intent(out) :: iret
817 call uptdd(id, lun, ient, iret)
829 function imrkopr_c(nemo)
result(ires) bind(C, name='imrkopr_f')
830 character(kind=c_char, len=1),
intent(in) :: nemo(*)
831 integer(c_int) :: ires
834 ires =
imrkopr(c_f_string(nemo))
846 function istdesc_c(idn)
result(ires) bind(C, name='istdesc_f')
847 integer(c_int),
intent(in),
value :: idn
848 integer(c_int) :: ires
865 subroutine ufbseq_c(bufr_unit, c_data, dim_1, dim_2, iret, table_d_mnemonic) bind(C, name='ufbseq_f')
866 integer(c_int),
value,
intent(in) :: bufr_unit
867 type(c_ptr),
intent(inout) :: c_data
868 integer(c_int),
value,
intent(in) :: dim_1, dim_2
869 integer(c_int),
intent(out) :: iret
870 character(kind=c_char, len=1),
intent(in) :: table_d_mnemonic(*)
871 real,
pointer :: f_data
873 call c_f_pointer(c_data, f_data)
874 call ufbseq(bufr_unit, f_data, dim_1, dim_2, iret, c_f_string(table_d_mnemonic))
891 function ireadns_c(bufr_unit, c_subset, iddate, subset_str_len)
result(ires) bind(C, name='ireadns_f')
892 integer(c_int),
value,
intent(in) :: bufr_unit
893 character(kind=c_char, len=1),
intent(out) :: c_subset(*)
894 integer(c_int),
intent(out) :: iddate
895 integer(c_int),
value,
intent(in) :: subset_str_len
896 integer(c_int) :: ires
897 character(len=25) :: f_subset
900 ires =
ireadns(bufr_unit, f_subset, iddate)
903 call copy_f_c_str(f_subset, c_subset, subset_str_len)
916 function ibfms_c(r8val)
result(ires) bind(C, name='ibfms_f')
917 real(c_double),
intent(in),
value :: r8val
918 integer(c_int) :: ires
933 subroutine strnum_c(str,num,iret) bind(C, name='strnum_f')
934 character(kind=c_char, len=1),
intent(in) :: str(*)
935 integer(c_int),
intent(out) :: num, iret
937 call strnum(c_f_string(str), num, iret)
951 subroutine stntbi_c(n,lun,numb,nemo,celsq) bind(C, name='stntbi_f')
952 integer(c_int),
intent(in),
value :: n, lun
953 character(kind=c_char, len=1),
intent(in) :: numb(*), nemo(*), celsq(*)
954 character(len=6) :: numb_f
955 character(len=8) :: nemo_f
956 character(len=55) :: celsq_f
960 numb_f(ii:ii) = numb(1)(ii:ii)
963 nemo_f(ii:ii) = nemo(1)(ii:ii)
966 celsq_f(ii:ii) = celsq(1)(ii:ii)
968 call stntbi(n, lun, numb_f, nemo_f, celsq_f)
981 function igettdi_c(iflag)
result(ires) bind(C, name='igettdi_f')
982 integer(c_int),
intent(in),
value :: iflag
983 integer(c_int) :: ires
1001 subroutine pktdd_c(id, lun, idn, iret) bind(C, name='pktdd_f')
1002 integer(c_int),
intent(in),
value :: id, lun, idn
1003 integer(c_int),
intent(out) :: iret
1005 call pktdd(id, lun, idn, iret)
1015 subroutine bort_c(errstr) bind(C, name='bort_f')
1016 character(kind=c_char, len=1),
intent(in) :: errstr(*)
1018 call bort(c_f_string(errstr))
1031 subroutine openmb_c(bufr_unit, c_subset, iddate) bind(C, name='openmb_f')
1032 integer(c_int),
value,
intent(in) :: bufr_unit, iddate
1033 character(kind=c_char, len=1),
intent(in) :: c_subset(*)
1035 call openmb(bufr_unit, c_f_string(c_subset), iddate)
1046 subroutine bvers_c(cverstr, cverstr_len) bind(C, name='bvers_f')
1047 character(kind=c_char, len=1),
intent(out) :: cverstr(*)
1048 integer(c_int),
value,
intent(in) :: cverstr_len
1049 character(len=10) :: f_cverstr
1051 call bvers(f_cverstr)
1052 call copy_f_c_str(f_cverstr, cverstr, cverstr_len)
1075 function iupb_c(mbay,nbyt,nbit)
result(ires) bind(C, name='iupb_f')
1076 integer(c_int),
intent(in) :: mbay(*)
1077 integer(c_int),
intent(in),
value :: nbyt, nbit
1078 integer(c_int) :: ires
1081 ires =
iupb(mbay,nbyt,nbit)
1092 subroutine cmpmsg_c(cf) bind(C, name='cmpmsg_f')
1093 character(kind=c_char, len=1),
intent(in) :: cf(*)
1095 call cmpmsg(c_f_string(cf))
1096 end subroutine cmpmsg_c
subroutine bort(STR)
Log one error message and abort application program.
subroutine bvers(CVERSTR)
Get the version number of the NCEPLIBS-bufr software.
subroutine cadn30(IDN, ADN)
Convert an FXY value from its WMO bit-wise representation to its six-character representation.
recursive subroutine closbf(LUNIT)
Close the connection between logical unit LUNIT and the NCEPLIBS-bufr software.
subroutine cmpmsg(CF)
Specify the use of compression when writing BUFR messages.
subroutine elemdx(CARD, LUN)
This subroutine decodes the scale factor, reference value, bit width and units (i....
recursive subroutine exitbufr
This subroutine frees all dynamically-allocated memory, closes all logical units that are open within...
integer function ibfms(R8VAL)
Test whether a real*8 data value is "missing".
function ifxy(ADSC)
Convert an FXY value from its 6 character representation to its WMO bit-wise representation.
recursive function igetmxby()
Get the maximum length of a BUFR message that can be written to an output file.
function igetntbi(LUN, CTB)
This function returns the next available index for storing an entry within a specified internal DX BU...
integer function igetprm(CPRMNM)
Get the current value of a parameter.
function igettdi(IFLAG)
Get the next usable Table D index for the current master table, or reset the index.
integer function imrkopr(NEMO)
Check whether a specified mnemonic is a Table C marker operator.
recursive function ireadmg(LUNIT, SUBSET, IDATE)
Calls NCEPLIBS-bufr subroutine readmg() and passes back its return code as the function value.
recursive function ireadns(LUNIT, SUBSET, IDATE)
Read the next data subset from a BUFR file that was previously opened for reading.
recursive function ireadsb(LUNIT)
Calls NCEPLIBS-bufr subroutine readsb() and passes back its return code as the function value.
recursive function isetprm(CPRMNM, IPVAL)
Define a customized parameter value for dynamic allocation.
function istdesc(IDN)
Check whether a descriptor is WMO-standard.
recursive function iupb(MBAY, NBYT, NBIT)
Decode an integer value from an integer array.
recursive function iupbs01(MBAY, S01MNEM)
Read a data value from Section 0 or Section 1 of a BUFR message.
recursive subroutine maxout(MAXO)
This subroutine allows the user to define the maximum length of a BUFR message that can be written to...
recursive subroutine mtinfo(CMTDIR, LUNMT1, LUNMT2)
Specify the directory location and Fortran logical unit numbers to be used when reading master BUFR t...
Wrap Fortran NCEPLIBS-bufr subprograms and variables so they can be called from within C.
subroutine, public get_isc_c(isc_ptr, isc_size)
Get copy of the moda_tables ISC array.
subroutine, public open_c(lunit, filepath)
Open a Fortran file from a C program.
integer(c_int) function, public ifxy_c(cfxy)
Convert an FXY value from its 6 character representation to its WMO bit-wise representation.
subroutine, public get_nval_c(lun, num_nodes)
Get the number of values in the current subset.
subroutine, public stntbi_c(n, lun, numb, nemo, celsq)
Store a new entry within the internal BUFR Table B or D.
subroutine, public status_c(file_unit, lun, il, im)
Check whether a file is connected to the library.
integer(c_int) function, public ireadmg_c(bufr_unit, c_subset, iddate, subset_str_len)
Read the next message from a BUFR file.
integer(c_int) function, public igetprm_c(cprmnm)
Get the current value of a parameter.
subroutine, public closbf_c(bufr_unit)
Close a previously opened file and disconnect it from the library.
subroutine, public close_c(lunit)
Close a Fortran file from a C program.
integer(c_int) function, public ibfms_c(r8val)
Test whether a data value is "missing".
subroutine, public ufbint_c(bufr_unit, c_data, dim_1, dim_2, iret, table_b_mnemonic)
Read/write one or more data values from/to a data subset.
subroutine, public mtinfo_c(path, file_unit_1, file_unit_2)
Specify location of master BUFR tables on local file system.
integer(c_int) function, public igetntbi_c(lun, table_type)
Get the next index for storing an entry within an internal DX BUFR table.
subroutine, public ufbrep_c(bufr_unit, c_data, dim_1, dim_2, iret, table_b_mnemonic)
Read/write one or more data values from/to a data subset.
integer(c_int) function, public iupbs01_c(bufr, mnemonic)
Read a data value from Section 0 or Section 1 of a BUFR message.
subroutine, public nemspecs_c(file_unit, mnemonic, mnemonic_idx, scale, reference, bits, iret)
Get the scale factor, reference value and bit width associated with a specified occurrence of a Table...
subroutine, public exitbufr_c()
Reset the library.
integer(c_int) function, public igettdi_c(iflag)
Get the next usable Table D index for the current master table, or reset the index.
subroutine, public get_inv_c(lun, inv_ptr, inv_size)
Get pointer to the moda_usrint INV array.
subroutine, public get_tag_c(tag_ptr, tag_len, mem_size)
Get copy of the moda_tables TAG array.
subroutine, public cadn30_c(idn, adn, adn_str_len)
Convert an FXY value from its WMO bit-wise representation to its six-character representation.
subroutine, public openbf_c(bufr_unit, cio, table_file_id)
Connect a new file to the library, or initialize the library, or change verbosity associated with alr...
subroutine, public bort_c(errstr)
Log one error message and abort application program.
integer(c_int) function, public istdesc_c(idn)
Check whether a descriptor is WMO-standard.
subroutine, public nemdefs_c(file_unit, mnemonic, unit_c, unit_str_len, desc_c, desc_str_len, iret)
Get the element name and units associated with a Table B mnemonic.
subroutine, public get_typ_c(typ_ptr, typ_len, mem_size)
Get copy of the moda_tables TYP array.
integer(c_int) function, public ireadns_c(bufr_unit, c_subset, iddate, subset_str_len)
Read the next data subset from a BUFR file.
subroutine, public pktdd_c(id, lun, idn, iret)
Store information about a child mnemonic within the internal arrays.
subroutine, public elemdx_c(card, lun)
Decode the scale factor, reference value, bit width, and units from a Table B mnemonic definition.
subroutine, public uptdd_c(id, lun, ient, iret)
Get the WMO bit-wise representation of the FXY value corresponding to a child mnemonic of a Table D s...
integer(c_int) function, public imrkopr_c(nemo)
Check whether a specified mnemonic is a Table C marker operator.
subroutine, public maxout_c(max0)
Define a customized maximum length for output BUFR messages.
subroutine, public get_jmpb_c(jmpb_ptr, jmpb_size)
Get copy of the moda_tables JMPB array.
subroutine, public openmb_c(bufr_unit, c_subset, iddate)
Open a new message for output in a BUFR file that was previously opened for writing.
subroutine, public get_inode_c(lun, start_node)
Get the bufr node idx for the start node of the subset.
subroutine, public delete_table_data_c()
Deletes the copies of the moda_tables arrays.
subroutine, public numtbd_c(lun, idn, nemo, nemo_str_len, tab, iret)
Search for a Table B or Table D descriptor within the internal DX BUFR tables.
subroutine, public nemtab_c(lun, mnemonic, descriptor, table_type, table_idx)
Get information about a descriptor.
integer(c_int) function, public ireadsb_c(bufr_unit)
Read the next data subset from a BUFR message.
subroutine, public get_link_c(link_ptr, link_size)
Get copy of the moda_tables LINK array.
integer(c_int) function, public iupb_c(mbay, nbyt, nbit)
Decode an integer value from an integer array.
subroutine, public wrdlen_c()
Determine important information about the local machine.
integer(c_int) function, public isetprm_c(cprmnm, ipval)
Define a customized parameter value for dynamic allocation.
subroutine, public bvers_c(cverstr, cverstr_len)
Get the version number of the NCEPLIBS-bufr software.
subroutine, public get_itp_c(itp_ptr, itp_size)
Get copy of the moda_tables ITP array.
subroutine, public nemtbb_c(lun, table_idx, unit_str, unit_str_len, scale, reference, bits)
Get information about a Table B descriptor.
subroutine, public ufbseq_c(bufr_unit, c_data, dim_1, dim_2, iret, table_d_mnemonic)
Read/write an entire sequence of data values from/to a data subset.
integer(c_int) function, public igetmxby_c()
Get the maximum length of a BUFR message that can be written to an output file.
subroutine, public get_irf_c(irf_ptr, irf_size)
Get copy of the moda_tables IRF array.
subroutine, public get_val_c(lun, val_ptr, val_size)
Get pointer to the moda_usrint VAL array.
subroutine, public strnum_c(str, num, iret)
Decode an integer from a character string.
This module contains declarations for arrays used to store information about the current BUFR message...
integer, dimension(:), allocatable inode
Table A mnemonic for type of BUFR message.
This module contains array and variable declarations used to store the internal jump/link table.
integer, dimension(:), allocatable irf
Reference values corresponding to tag and typ:
integer, dimension(:), allocatable isc
Scale factors corresponding to tag and typ:
character *3, dimension(:), allocatable typ
Type indicators corresponding to tag:
integer, dimension(:), allocatable jmpb
Jump backward indices corresponding to tag and typ:
character *10, dimension(:), allocatable tag
Mnemonics in the jump/link table.
integer ntab
Number of entries in the jump/link table.
integer, dimension(:), allocatable itp
Integer type values corresponding to typ:
integer, dimension(:), allocatable link
Link indices corresponding to tag, typ and jmpb:
This module contains declarations for arrays used to store data values and associated metadata for th...
integer, dimension(:), allocatable nval
Number of data values in BUFR data subset.
real *8, dimension(:,:), allocatable, target val
Data values.
integer, dimension(:,:), allocatable, target inv
Inventory pointer which links each data value to its corresponding node in the internal jump/link tab...
recursive subroutine nemdefs(LUNIT, NEMO, CELEM, CUNIT, IRET)
Given a Table B mnemonic defined in the DX BUFR Tables associated with a BUFR file (or in the master ...
recursive subroutine nemspecs(LUNIT, NEMO, NNEMO, NSCL, NREF, NBTS, IRET)
Given a Table B mnemonic defined within a data subset, this subroutine returns the scale factor,...
subroutine nemtab(LUN, NEMO, IDN, TAB, IRET)
Get information about a descriptor, based on the mnemonic.
subroutine nemtbb(LUN, ITAB, UNIT, ISCL, IREF, IBIT)
Get information about a Table B descriptor.
subroutine numtbd(LUN, IDN, NEMO, TAB, IRET)
Search for a Table B or Table D descriptor within the internal DX BUFR tables.
recursive subroutine openbf(LUNIT, IO, LUNDX)
Connects a new file to the NCEPLIBS-bufr software for input or output operations, or initializes the ...
recursive subroutine openmb(LUNIT, SUBSET, JDATE)
Open a new message for output in a BUFR file that was previously opened for writing.
subroutine pktdd(ID, LUN, IDN, IRET)
Store information about a child mnemonic within the internal arrays.
recursive subroutine status(LUNIT, LUN, IL, IM)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
subroutine stntbi(N, LUN, NUMB, NEMO, CELSQ)
Store a new entry within the internal BUFR Table B or D.
recursive subroutine strnum(str, num, iret)
Decode an integer from a character string.
recursive subroutine ufbint(LUNIN, USR, I1, I2, IRET, STR)
Read/write one or more data values from/to a data subset.
recursive subroutine ufbrep(LUNIN, USR, I1, I2, IRET, STR)
Read/write one or more data values from/to a data subset.
recursive subroutine ufbseq(LUNIN, USR, I1, I2, IRET, STR)
This subroutine reads or writes an entire sequence of data values from or to the BUFR data subset tha...
subroutine uptdd(ID, LUN, IENT, IRET)
Returns the WMO bit-wise representation of the FXY value corresponding to a child mnemonic of a Table...
subroutine wrdlen
Determine important information about the local machine.