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(:)
50 function get_c_string_length(c_str)
result(nchars)
51 character(kind=c_char, len=1),
intent(in) :: c_str(*)
55 do while (c_str(nchars) /= c_null_char)
59 end function get_c_string_length
71 function c_f_string(c_str)
result(f_str)
72 character(kind=c_char, len=1),
intent(in) :: c_str(*)
73 character(len=:),
allocatable :: f_str
76 nchars = get_c_string_length(c_str)
78 allocate(
character(len=nchars) :: f_str)
79 f_str = transfer(c_str(1:nchars), f_str)
80 end function c_f_string
89 subroutine copy_f_c_str(f_str, c_str, c_str_len)
90 character(len=*),
target,
intent(in) :: f_str
91 character(kind=c_char),
intent(inout) :: c_str(*)
92 integer,
intent(in) :: c_str_len
95 if (c_str_len /= 0)
then
97 c_str(ii) = f_str(ii:ii)
99 c_str(c_str_len) = c_null_char
101 end subroutine copy_f_c_str
109 subroutine open_c(lunit, filepath) bind(C, name='open_f')
110 integer(c_int),
value,
intent(in) :: lunit
111 character(kind=c_char) :: filepath
113 open(lunit, file=c_f_string(filepath))
121 subroutine close_c(lunit) bind(C, name='close_f')
122 integer(c_int),
value,
intent(in) :: lunit
137 recursive subroutine openbf_c(bufr_unit, cio, table_file_id) bind(C, name='openbf_f')
138 integer(c_int),
value,
intent(in) :: bufr_unit, table_file_id
139 character(kind=c_char),
intent(in) :: cio(*)
140 character(len=5) :: io
143 lio = get_c_string_length(cio)
144 io = transfer(cio(1:lio), io)
145 call openbf(bufr_unit, io(1:lio), table_file_id)
155 recursive subroutine closbf_c(bufr_unit) bind(C, name='closbf_f')
156 integer(c_int),
value,
intent(in) :: bufr_unit
184 function ireadmg_c(bufr_unit, c_subset, iddate, subset_str_len)
result(ires) bind(C, name='ireadmg_f')
185 integer(c_int),
value,
intent(in) :: bufr_unit
186 character(kind=c_char),
intent(out) :: c_subset(*)
187 integer(c_int),
intent(out) :: iddate
188 integer(c_int),
value,
intent(in) :: subset_str_len
189 integer(c_int) :: ires
190 character(len=25) :: f_subset
193 ires =
ireadmg(bufr_unit, f_subset, iddate)
196 call copy_f_c_str(f_subset, c_subset, subset_str_len)
213 recursive subroutine readmg_c(bufr_unit, c_subset, iddate, subset_str_len, ires) bind(C, name='readmg_f')
214 integer(c_int),
value,
intent(in) :: bufr_unit
215 character(kind=c_char),
intent(out) :: c_subset(*)
216 integer(c_int),
intent(out) :: iddate, ires
217 integer(c_int),
value,
intent(in) :: subset_str_len
218 character(len=25) :: f_subset
220 call readmg(bufr_unit, f_subset, iddate, ires)
223 call copy_f_c_str(f_subset, c_subset, subset_str_len)
238 function ireadsb_c(bufr_unit)
result(ires) bind(C, name='ireadsb_f')
239 integer(c_int),
value,
intent(in) :: bufr_unit
240 integer(c_int) :: ires
256 recursive subroutine readsb_c(bufr_unit, ires) bind(C, name='readsb_f')
257 integer(c_int),
value,
intent(in) :: bufr_unit
258 integer(c_int),
intent(out) :: ires
260 call readsb(bufr_unit, ires)
274 recursive subroutine ufbint_c(bufr_unit, c_data, dim_1, dim_2, iret, table_b_mnemonic) bind(C, name='ufbint_f')
275 integer(c_int),
value,
intent(in) :: bufr_unit, dim_1, dim_2
276 type(c_ptr),
intent(inout) :: c_data
277 integer(c_int),
intent(out) :: iret
278 character(kind=c_char),
intent(in) :: table_b_mnemonic(*)
279 character(len=80) :: str
280 real,
pointer :: f_data
283 lstr = get_c_string_length(table_b_mnemonic)
284 str = transfer(table_b_mnemonic(1:lstr), str)
285 call c_f_pointer(c_data, f_data)
286 call ufbint(bufr_unit, f_data, dim_1, dim_2, iret, str(1:lstr))
300 subroutine ufbrep_c(bufr_unit, c_data, dim_1, dim_2, iret, table_b_mnemonic) bind(C, name='ufbrep_f')
301 integer(c_int),
value,
intent(in) :: bufr_unit, dim_1, dim_2
302 type(c_ptr),
intent(inout) :: c_data
303 integer(c_int),
intent(out) :: iret
304 character(kind=c_char),
intent(in) :: table_b_mnemonic(*)
305 character(len=80) :: str
306 real,
pointer :: f_data
309 lstr = get_c_string_length(table_b_mnemonic)
310 str = transfer(table_b_mnemonic(1:lstr), str)
311 call c_f_pointer(c_data, f_data)
312 call ufbrep(bufr_unit, f_data, dim_1, dim_2, iret, str(1:lstr))
324 subroutine mtinfo_c(path, file_unit_1, file_unit_2) bind(C, name='mtinfo_f')
325 character(kind=c_char),
intent(in) :: path(*)
326 integer(c_int),
value,
intent(in) :: file_unit_1, file_unit_2
327 character(len=240) :: mtdir
330 lmtdir = get_c_string_length(path)
331 mtdir = transfer(path(1:lmtdir), mtdir)
332 call mtinfo(mtdir(1:lmtdir), file_unit_1, file_unit_2)
345 subroutine status_c(file_unit, lun, il, im) bind(C, name='status_f')
346 integer(c_int),
value,
intent(in) :: file_unit
347 integer(c_int),
intent(out) :: lun
348 integer(c_int),
intent(out) :: il
349 integer(c_int),
intent(out) :: im
351 call status(file_unit, lun, il, im)
367 subroutine nemdefs_c(file_unit, mnemonic, unit_c, unit_str_len, desc_c, desc_str_len, iret) &
368 bind(c, name=
'nemdefs_f')
369 integer(c_int),
value,
intent(in) :: file_unit, unit_str_len, desc_str_len
370 character(kind=c_char),
intent(in) :: mnemonic(*)
371 character(kind=c_char),
intent(out) :: unit_c(*), desc_c(*)
372 integer(c_int),
intent(out) :: iret
373 character(len=25) :: unit_f
374 character(len=55) :: desc_f
375 character(len=10) :: tag
378 ltag = get_c_string_length(mnemonic)
379 tag = transfer(mnemonic(1:ltag), tag)
382 call nemdefs ( file_unit, tag(1:ltag), desc_f, unit_f, iret)
386 call copy_f_c_str(unit_f, unit_c, min(len(unit_f), unit_str_len))
388 call copy_f_c_str(desc_f, desc_c, min(len(desc_f), desc_str_len))
406 subroutine nemspecs_c(file_unit, mnemonic, mnemonic_idx, scale, reference, bits, iret) &
407 bind(c, name=
'nemspecs_f')
408 integer(c_int),
value,
intent(in) :: file_unit, mnemonic_idx
409 character(kind=c_char),
intent(in) :: mnemonic(*)
410 integer(c_int),
intent(out) :: scale, reference, bits, iret
411 character(len=10) :: tag
414 ltag = get_c_string_length(mnemonic)
415 tag = transfer(mnemonic(1:ltag), tag)
418 call nemspecs(file_unit, tag(1:ltag), mnemonic_idx, scale, reference, bits, iret)
432 subroutine nemtab_c(lun, mnemonic, descriptor, table_type, table_idx) &
433 bind(c, name=
'nemtab_f')
434 integer(c_int),
value,
intent(in) :: lun
435 character(kind=c_char),
intent(in) :: mnemonic(*)
436 integer(c_int),
intent(out) :: descriptor, table_idx
437 character(kind=c_char),
intent(out) :: table_type(*)
438 character(len=1) :: table_type_f
439 character(len=10) :: tag
442 ltag = get_c_string_length(mnemonic)
443 tag = transfer(mnemonic(1:ltag), tag)
445 call nemtab(lun, tag(1:ltag), descriptor, table_type_f, table_idx)
447 table_type(1) = table_type_f(1:1)
463 subroutine nemtbb_c(lun, table_idx, unit_str, unit_str_len, scale, reference, bits) &
464 bind(c, name=
'nemtbb_f')
465 integer(c_int),
intent(in),
value :: lun
466 integer(c_int),
intent(in),
value :: table_idx
467 character(kind=c_char),
intent(out) :: unit_str(*)
468 integer(c_int),
intent(in),
value :: unit_str_len
469 integer(c_int),
intent(out) :: scale
470 integer(c_int),
intent(out) :: reference
471 integer(c_int),
intent(out) :: bits
473 character(len=25) :: unit_str_f
476 call nemtbb( lun, table_idx, unit_str_f, scale, reference, bits)
477 call copy_f_c_str(unit_str_f, unit_str, min(len(unit_str_f), unit_str_len))
486 subroutine get_isc_c(isc_ptr, isc_size) bind(C, name='get_isc_f')
488 type(c_ptr),
intent(inout) :: isc_ptr
489 integer(c_int),
intent(out) :: isc_size
491 allocate(isc_f(
ntab))
493 isc_size =
size(isc_f)
494 isc_ptr = c_loc(isc_f(1))
503 subroutine get_link_c(link_ptr, link_size) bind(C, name='get_link_f')
505 type(c_ptr),
intent(inout) :: link_ptr
506 integer(c_int),
intent(out) :: link_size
508 allocate(link_f(
ntab))
510 link_size =
size(link_f)
511 link_ptr = c_loc(link_f(1))
520 subroutine get_itp_c(itp_ptr, itp_size) bind(C, name='get_itp_f')
522 type(c_ptr),
intent(inout) :: itp_ptr
523 integer(c_int),
intent(out) :: itp_size
525 allocate(itp_f(
ntab))
527 itp_size =
size(itp_f)
528 itp_ptr = c_loc(itp_f(1))
538 subroutine get_typ_c(typ_ptr, typ_len, mem_size) bind(C, name='get_typ_f')
540 type(c_ptr),
intent(inout) :: typ_ptr
541 integer(c_int),
intent(out) :: typ_len
542 integer(c_int),
intent(out) :: mem_size
544 allocate(typ_f(
ntab))
546 typ_len = len(
typ(1))
547 mem_size =
size(typ_f)
548 typ_ptr = c_loc(typ_f(1))
558 subroutine get_tag_c(tag_ptr, tag_len, mem_size) bind(C, name='get_tag_f')
560 type(c_ptr),
intent(inout) :: tag_ptr
561 integer(c_int),
intent(out) :: tag_len
562 integer(c_int),
intent(out) :: mem_size
564 allocate(tag_f(
ntab))
566 tag_len = len(
tag(1))
567 mem_size =
size(tag_f)
568 tag_ptr = c_loc(tag_f(1))
577 subroutine get_jmpb_c(jmpb_ptr, jmpb_size) bind(C, name='get_jmpb_f')
579 type(c_ptr),
intent(inout) :: jmpb_ptr
580 integer(c_int),
intent(out) :: jmpb_size
582 allocate(jmpb_f(
ntab))
584 jmpb_size =
size(jmpb_f)
585 jmpb_ptr = c_loc(jmpb_f(1))
594 subroutine get_irf_c(irf_ptr, irf_size) bind(C, name='get_irf_f')
596 type(c_ptr),
intent(inout) :: irf_ptr
597 integer(c_int),
intent(out) :: irf_size
599 allocate(irf_f(
ntab))
601 irf_size =
size(irf_f)
602 irf_ptr = c_loc(irf_f(1))
611 subroutine get_inode_c(lun, start_node) bind(C, name='get_inode_f')
613 integer(c_int),
value,
intent(in) :: lun
614 integer(c_int),
intent(out) :: start_node
616 start_node =
inode(lun)
625 subroutine get_nval_c(lun, num_nodes) bind(C, name='get_nval_f')
627 integer(c_int),
value,
intent(in) :: lun
628 integer(c_int),
intent(out) :: num_nodes
630 num_nodes =
nval(lun)
640 subroutine get_val_c(lun, val_ptr, val_size) bind(C, name='get_val_f')
642 integer(c_int),
value,
intent(in) :: lun
643 type(c_ptr),
intent(inout) :: val_ptr
644 integer(c_int),
intent(out) :: val_size
646 val_size =
size(
val(:, lun))
647 val_ptr = c_loc(
val(1, lun))
657 subroutine get_inv_c(lun, inv_ptr, inv_size) bind(C, name='get_inv_f')
659 integer(c_int),
value,
intent(in) :: lun
660 type(c_ptr),
intent(inout) :: inv_ptr
661 integer(c_int),
intent(out) :: inv_size
663 inv_size =
size(
inv(:, lun))
664 inv_ptr = c_loc(
inv(1, lun))
676 subroutine readlc_c(lunit, str_id, output_str, output_str_len) bind(C, name='readlc_f')
678 integer(c_int),
value,
intent(in) :: lunit, output_str_len
679 character(kind=c_char),
intent(in) :: str_id(*)
680 character(kind=c_char),
intent(out) :: output_str(*)
681 character(len=120) :: output_str_f
682 character(len=14) :: str
683 integer :: output_str_len_f, lstr
685 lstr = get_c_string_length(str_id)
686 str = transfer(str_id(1:lstr), str)
688 call readlc(lunit, output_str_f, str(1:lstr))
690 output_str_len_f = len(trim(output_str_f)) + 1
691 call copy_f_c_str(output_str_f, output_str, min(output_str_len_f, output_str_len))
698 if (
allocated(isc_f))
deallocate(isc_f)
699 if (
allocated(link_f))
deallocate(link_f)
700 if (
allocated(itp_f))
deallocate(itp_f)
701 if (
allocated(typ_f))
deallocate(typ_f)
702 if (
allocated(tag_f))
deallocate(tag_f)
703 if (
allocated(jmpb_f))
deallocate(jmpb_f)
704 if (
allocated(irf_f))
deallocate(irf_f)
719 function iupbs01_c(bufr, mnemonic)
result(ires) bind(C, name='iupbs01_f')
720 integer(c_int),
intent(in) :: bufr(*)
721 character(kind=c_char),
intent(in) :: mnemonic(*)
722 integer(c_int) :: ires
724 character(len=10) :: tag
726 ltag = get_c_string_length(mnemonic)
727 tag = transfer(mnemonic(1:ltag), tag)
729 ires =
iupbs01(bufr,tag(1:ltag))
742 function igetprm_c(cprmnm)
result(ires) bind(C, name='igetprm_f')
743 character(kind=c_char),
intent(in) :: cprmnm(*)
744 integer(c_int) :: ires
747 ires =
igetprm(c_f_string(cprmnm))
760 function isetprm_c(cprmnm,ipval)
result(ires) bind(C, name='isetprm_f')
761 character(kind=c_char),
intent(in) :: cprmnm(*)
762 integer(c_int),
value,
intent(in) :: ipval
763 integer(c_int) :: ires
766 ires =
isetprm(c_f_string(cprmnm),ipval)
778 integer(c_int),
value,
intent(in) :: max0
792 function igetmxby_c()
result(ires) bind(C, name='igetmxby_f')
793 integer(c_int) :: ires
809 subroutine cadn30_c(idn, adn, adn_str_len) bind(C, name='cadn30_f')
810 integer(c_int),
intent(in),
value :: idn, adn_str_len
811 character(kind=c_char),
intent(out) :: adn(*)
812 character(len=8) :: adn_f
815 call copy_f_c_str(adn_f, adn, adn_str_len)
828 function igetntbi_c(lun, table_type)
result(ires) bind(C, name='igetntbi_f')
829 integer(c_int),
value,
intent(in) :: lun
830 character(kind=c_char),
intent(in) :: table_type(*)
831 integer(c_int) :: ires
833 character(len=1) :: table_type_f
835 table_type_f(1:1) = table_type(1)(1:1)
849 subroutine elemdx_c(card,lun) bind(C, name='elemdx_f')
850 integer(c_int),
value,
intent(in) :: lun
851 character(kind=c_char),
intent(in) :: card(*)
852 character(len=80) :: card_f
856 card_f(ii:ii) = card(ii)
873 subroutine numtbd_c(lun,idn,nemo,nemo_str_len,tab,iret) bind(C, name='numtbd_f')
874 integer(c_int),
value,
intent(in) :: lun, idn, nemo_str_len
875 character(kind=c_char),
intent(out) :: nemo(*), tab(*)
876 integer(c_int),
intent(out) :: iret
878 character(len=9) :: nemo_f
879 character(len=1) :: tab_f
881 call numtbd(lun, idn, nemo_f, tab_f, iret)
883 call copy_f_c_str(nemo_f, nemo, nemo_str_len)
897 function ifxy_c(cfxy)
result(ires) bind(C, name='ifxy_f')
898 character(kind=c_char),
intent(in) :: cfxy(*)
899 integer(c_int) :: ires
902 ires =
ifxy(c_f_string(cfxy))
921 subroutine uptdd_c(id, lun, ient, iret) bind(C, name='uptdd_f')
922 integer(c_int),
intent(in),
value :: id, lun, ient
923 integer(c_int),
intent(out) :: iret
925 call uptdd(id, lun, ient, iret)
937 function imrkopr_c(nemo)
result(ires) bind(C, name='imrkopr_f')
938 character(kind=c_char),
intent(in) :: nemo(*)
939 integer(c_int) :: ires
942 ires =
imrkopr(c_f_string(nemo))
954 function istdesc_c(idn)
result(ires) bind(C, name='istdesc_f')
955 integer(c_int),
intent(in),
value :: idn
956 integer(c_int) :: ires
973 subroutine ufbseq_c(bufr_unit, c_data, dim_1, dim_2, iret, table_d_mnemonic) bind(C, name='ufbseq_f')
974 integer(c_int),
value,
intent(in) :: bufr_unit, dim_1, dim_2
975 type(c_ptr),
intent(inout) :: c_data
976 integer(c_int),
intent(out) :: iret
977 character(kind=c_char),
intent(in) :: table_d_mnemonic(*)
978 character(len=80) :: str
979 real,
pointer :: f_data
982 lstr = get_c_string_length(table_d_mnemonic)
983 str = transfer(table_d_mnemonic(1:lstr), str)
984 call c_f_pointer(c_data, f_data)
985 call ufbseq(bufr_unit, f_data, dim_1, dim_2, iret, str(1:lstr))
1002 function ireadns_c(bufr_unit, c_subset, iddate, subset_str_len)
result(ires) bind(C, name='ireadns_f')
1003 integer(c_int),
value,
intent(in) :: bufr_unit
1004 character(kind=c_char),
intent(out) :: c_subset(*)
1005 integer(c_int),
intent(out) :: iddate
1006 integer(c_int),
value,
intent(in) :: subset_str_len
1007 integer(c_int) :: ires
1008 character(len=25) :: f_subset
1011 ires =
ireadns(bufr_unit, f_subset, iddate)
1014 call copy_f_c_str(f_subset, c_subset, subset_str_len)
1031 recursive subroutine readns_c(bufr_unit, c_subset, iddate, subset_str_len, ires) bind(C, name='readns_f')
1032 integer(c_int),
value,
intent(in) :: bufr_unit
1033 character(kind=c_char),
intent(out) :: c_subset(*)
1034 integer(c_int),
intent(out) :: iddate, ires
1035 integer(c_int),
value,
intent(in) :: subset_str_len
1036 character(len=25) :: f_subset
1038 call readns(bufr_unit, f_subset, iddate, ires)
1041 call copy_f_c_str(f_subset, c_subset, subset_str_len)
1054 function ibfms_c(r8val)
result(ires) bind(C, name='ibfms_f')
1055 real(c_double),
intent(in),
value :: r8val
1056 integer(c_int) :: ires
1071 subroutine strnum_c(str,num,iret) bind(C, name='strnum_f')
1072 character(kind=c_char),
intent(in) :: str(*)
1073 integer(c_int),
intent(out) :: num, iret
1075 call strnum(c_f_string(str), num, iret)
1089 subroutine stntbi_c(n,lun,numb,nemo,celsq) bind(C, name='stntbi_f')
1090 integer(c_int),
intent(in),
value :: n, lun
1091 character(kind=c_char),
intent(in) :: numb(*), nemo(*), celsq(*)
1092 character(len=6) :: numb_f
1093 character(len=8) :: nemo_f
1094 character(len=55) :: celsq_f
1098 numb_f(ii:ii) = numb(ii)
1101 nemo_f(ii:ii) = nemo(ii)
1104 celsq_f(ii:ii) = celsq(ii)
1106 call stntbi(n, lun, numb_f, nemo_f, celsq_f)
1119 function igettdi_c(iflag)
result(ires) bind(C, name='igettdi_f')
1120 integer(c_int),
intent(in),
value :: iflag
1121 integer(c_int) :: ires
1139 subroutine pktdd_c(id, lun, idn, iret) bind(C, name='pktdd_f')
1140 integer(c_int),
intent(in),
value :: id, lun, idn
1141 integer(c_int),
intent(out) :: iret
1143 call pktdd(id, lun, idn, iret)
1153 subroutine bort_c(errstr) bind(C, name='bort_f')
1154 character(kind=c_char),
intent(in) :: errstr(*)
1156 call bort(c_f_string(errstr))
1169 subroutine openmb_c(bufr_unit, c_subset, iddate) bind(C, name='openmb_f')
1170 integer(c_int),
value,
intent(in) :: bufr_unit, iddate
1171 character(kind=c_char),
intent(in) :: c_subset(*)
1172 character(len=8) :: f_subset
1175 lfs = get_c_string_length(c_subset)
1176 f_subset = transfer(c_subset(1:lfs), f_subset)
1178 call openmb(bufr_unit, f_subset(1:lfs), iddate)
1189 subroutine bvers_c(cverstr, cverstr_len) bind(C, name='bvers_f')
1190 character(kind=c_char),
intent(out) :: cverstr(*)
1191 integer(c_int),
value,
intent(in) :: cverstr_len
1192 character(len=10) :: f_cverstr
1194 call bvers(f_cverstr)
1195 call copy_f_c_str(f_cverstr, cverstr, cverstr_len)
1206 subroutine cmpmsg_c(cf) bind(C, name='cmpmsg_f')
1207 character(kind=c_char),
intent(in) :: cf(*)
1212 end subroutine cmpmsg_c
integer function igetprm(cprmnm)
Return the current value of a parameter used for allocating one or more internal arrays within the NC...
subroutine exitbufr
Free all dynamically-allocated memory, close all logical units that are open within the NCEPLIBS-bufr...
recursive integer function isetprm(cprmnm, ipval)
Set a specified parameter to a specified value for use in dynamically allocating one or more internal...
integer function imrkopr(nemo)
Check whether a specified mnemonic is a Table C marker operator.
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
subroutine cmpmsg(cf)
Specify whether BUFR messages output by future calls to message-writing subroutines and subset-writin...
subroutine elemdx(card, lun)
Decode the scale factor, reference value, bit width and units (i.e., the "elements") from a Table B m...
subroutine nemtbb(lun, itab, unit, iscl, iref, ibit)
Get information about a Table B descriptor from the internal DX BUFR tables.
subroutine stntbi(n, lun, numb, nemo, celsq)
Store a new entry within internal BUFR Table B or D.
subroutine pktdd(id, lun, idn, iret)
Store information about a child mnemonic within the internal BUFR Table D.
recursive subroutine nemdefs(lunit, nemo, celem, cunit, iret)
Get the element name and units associated with a Table B descriptor.
integer function igetntbi(lun, ctb)
Get the next available index for storing an entry within a specified internal DX BUFR table.
subroutine uptdd(id, lun, ient, iret)
Get the WMO bit-wise representation of the FXY value corresponding to a child mnemonic in a Table D s...
subroutine nemtab(lun, nemo, idn, tab, iret)
Get information about a descriptor, based on a mnemonic.
subroutine cadn30(idn, adn)
Convert an FXY value from its WMO bit-wise representation to its 6 character representation.
subroutine numtbd(lun, idn, nemo, tab, iret)
Get information about a Table B or Table D descriptor, based on the WMO bit-wise representation of an...
integer function ifxy(adsc)
Convert an FXY value from its 6 character representation to its WMO bit-wise representation.
recursive subroutine nemspecs(lunit, nemo, nnemo, nscl, nref, nbts, iret)
Get the scale factor, reference value and bit width associated with a specified occurrence of a Table...
integer function igettdi(iflag)
Depending on the value of the input flag, either return the next usable scratch Table D index for the...
recursive subroutine mtinfo(cmtdir, lunmt1, lunmt2)
Specify the directory location and Fortran logical unit numbers to be used when reading master BUFR t...
subroutine bvers(cverstr)
Get the version number of the NCEPLIBS-bufr software.
recursive subroutine strnum(str, num, iret)
Decode an integer from a character string.
integer function ibfms(r8val)
Check whether a real*8 data value returned from a previous call to any of the NCEPLIBS-bufr values-re...
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.
recursive subroutine, public readsb_c(bufr_unit, ires)
Read the next data subset from a BUFR message.
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.
recursive subroutine, public readmg_c(bufr_unit, c_subset, iddate, subset_str_len, ires)
Read the next message from a BUFR file.
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 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 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 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.
recursive 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 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.
recursive 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 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.
subroutine, public readlc_c(lunit, str_id, output_str, output_str_len)
Function used to get long strings from the BUFR file.
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.
recursive subroutine, public readns_c(bufr_unit, c_subset, iddate, subset_str_len, ires)
Read the next data subset from a BUFR file.
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.
recursive subroutine, public closbf_c(bufr_unit)
Close a previously opened file and disconnect it from the library.
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.
Declare arrays used to store information about the current BUFR message that is in the process of bei...
integer, dimension(:), allocatable inode
Table A mnemonic for type of BUFR message.
Declare arrays and variables needed to store information about long character strings (greater than 8...
Declare arrays and variables 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:
Declare arrays used to store data values and associated metadata for the current BUFR data subset in ...
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 closbf(lunit)
Close the connection between logical unit lunit and the NCEPLIBS-bufr software.
recursive subroutine openbf(lunit, io, lundx)
Connect a new file to the NCEPLIBS-bufr software for input or output operations, or initialize the li...
recursive subroutine status(lunit, lun, il, im)
Check whether a specified Fortran logical unit number is currently connected to the NCEPLIBS-bufr sof...
recursive subroutine maxout(maxo)
Specify the maximum length of a BUFR message that can be written to any output file by the NCEPLIBS-b...
recursive subroutine openmb(lunit, subset, jdate)
Open and initialize a new BUFR message within internal arrays, for eventual output to logical unit lu...
integer function igetmxby()
Get the maximum length of a BUFR message that can be written to an output file by the NCEPLIBS-bufr s...
recursive subroutine readmg(lunxx, subset, jdate, iret)
Read the next BUFR message from logical unit abs(lunxx) into internal arrays.
recursive integer function ireadmg(lunit, subset, idate)
Call subroutine readmg() and pass back its return code as the function value.
recursive integer function ireadns(lunit, subset, idate)
Call subroutine readns() and pass back its return code as the function value.
recursive integer function ireadsb(lunit)
Call subroutine readsb() and pass back its return code as the function value.
recursive subroutine readsb(lunit, iret)
Read the next data subset from a BUFR message.
recursive subroutine readns(lunit, subset, jdate, iret)
Read the next data subset from a BUFR file.
recursive subroutine ufbseq(lunin, usr, i1, i2, iret, str)
Read or write an entire sequence of data values from or to a data subset.
recursive subroutine ufbint(lunin, usr, i1, i2, iret, str)
Read or write one or more data values from or to a data subset.
recursive subroutine readlc(lunit, chr, str)
Read a long character string (greater than 8 bytes) from a data subset.
recursive subroutine ufbrep(lunin, usr, i1, i2, iret, str)
Read or write one or more data values from or to a data subset.
recursive integer function iupbs01(mbay, s01mnem)
Read a specified value from within Section 0 or Section 1 of a BUFR message.
integer function istdesc(idn)
Given the WMO bit-wise representation of an FXY value for a descriptor, check whether the descriptor ...