NCEPLIBS-bufr  12.2.0
bufr_c2f_interface.F90
Go to the documentation of this file.
1 
6 
17 
18  use iso_c_binding
19 
20  implicit none
21 
22  private
23  public :: open_c, close_c, openbf_c, closbf_c
26  public :: ufbint_c, ufbrep_c, ufbseq_c
27  public :: mtinfo_c, bvers_c, status_c, ibfms_c
30  public :: delete_table_data_c
31  public :: iupbs01_c, imrkopr_c, istdesc_c, ifxy_c
32  public :: igetntbi_c, igettdi_c, stntbi_c
36 
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(:)
40 
41  contains
42 
50  function get_c_string_length(c_str) result(nchars)
51  character(kind=c_char, len=1), intent(in) :: c_str(*)
52  integer :: nchars
53 
54  nchars = 1
55  do while (c_str(nchars) /= c_null_char)
56  nchars = nchars + 1
57  end do
58  nchars = nchars - 1
59  end function get_c_string_length
60 
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
74  integer :: nchars
75 
76  nchars = get_c_string_length(c_str)
77 
78  allocate(character(len=nchars) :: f_str)
79  f_str = transfer(c_str(1:nchars), f_str)
80  end function c_f_string
81 
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
93  integer :: ii
94 
95  if (c_str_len /= 0) then
96  do ii = 1, c_str_len
97  c_str(ii) = f_str(ii:ii)
98  enddo
99  c_str(c_str_len) = c_null_char
100  end if
101  end subroutine copy_f_c_str
102 
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
112 
113  open(lunit, file=c_f_string(filepath))
114  end subroutine open_c
115 
121  subroutine close_c(lunit) bind(C, name='close_f')
122  integer(c_int), value, intent(in) :: lunit
123 
124  close(unit=lunit)
125  end subroutine close_c
126 
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
141  integer :: lio
142 
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)
146  end subroutine openbf_c
147 
155  recursive subroutine closbf_c(bufr_unit) bind(C, name='closbf_f')
156  integer(c_int), value, intent(in) :: bufr_unit
157 
158  call closbf(bufr_unit)
159  end subroutine closbf_c
160 
166  subroutine exitbufr_c() bind(C, name='exitbufr_f')
167  call exitbufr()
168  end subroutine exitbufr_c
169 
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
191  integer :: ireadmg
192 
193  ires = ireadmg(bufr_unit, f_subset, iddate)
194 
195  if (ires == 0) then
196  call copy_f_c_str(f_subset, c_subset, subset_str_len)
197  end if
198  end function ireadmg_c
199 
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
219 
220  call readmg(bufr_unit, f_subset, iddate, ires)
221 
222  if (ires == 0) then
223  call copy_f_c_str(f_subset, c_subset, subset_str_len)
224  end if
225  end subroutine readmg_c
226 
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
241  integer :: ireadsb
242 
243  ires = ireadsb(bufr_unit)
244  end function ireadsb_c
245 
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
259 
260  call readsb(bufr_unit, ires)
261  end subroutine readsb_c
262 
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
281  integer :: lstr
282 
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))
287  end subroutine ufbint_c
288 
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
307  integer :: lstr
308 
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))
313  end subroutine ufbrep_c
314 
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
328  integer :: lmtdir
329 
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)
333  end subroutine mtinfo_c
334 
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
350 
351  call status(file_unit, lun, il, im)
352  end subroutine status_c
353 
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
376  integer :: ltag
377 
378  ltag = get_c_string_length(mnemonic)
379  tag = transfer(mnemonic(1:ltag), tag)
380 
381  ! Get the unit and description strings
382  call nemdefs ( file_unit, tag(1:ltag), desc_f, unit_f, iret)
383 
384  if (iret == 0) then
385  ! Copy the unit Fortran string into the resulting C-style string.
386  call copy_f_c_str(unit_f, unit_c, min(len(unit_f), unit_str_len))
387  ! Copy the descriptor Fortran string into the resulting C-style string.
388  call copy_f_c_str(desc_f, desc_c, min(len(desc_f), desc_str_len))
389  end if
390  end subroutine nemdefs_c
391 
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
412  integer :: ltag
413 
414  ltag = get_c_string_length(mnemonic)
415  tag = transfer(mnemonic(1:ltag), tag)
416 
417  ! Get the scale, reference and bits
418  call nemspecs(file_unit, tag(1:ltag), mnemonic_idx, scale, reference, bits, iret)
419  end subroutine nemspecs_c
420 
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
440  integer :: ltag
441 
442  ltag = get_c_string_length(mnemonic)
443  tag = transfer(mnemonic(1:ltag), tag)
444 
445  call nemtab(lun, tag(1:ltag), descriptor, table_type_f, table_idx)
446 
447  table_type(1) = table_type_f(1:1)
448  end subroutine nemtab_c
449 
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
472 
473  character(len=25) :: unit_str_f
474 
475  ! Get the scale, reference and bits
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))
478  end subroutine nemtbb_c
479 
486  subroutine get_isc_c(isc_ptr, isc_size) bind(C, name='get_isc_f')
487  use moda_tables
488  type(c_ptr), intent(inout) :: isc_ptr
489  integer(c_int), intent(out) :: isc_size
490 
491  allocate(isc_f(ntab))
492  isc_f(1:ntab) = isc(1:ntab)
493  isc_size = size(isc_f)
494  isc_ptr = c_loc(isc_f(1))
495  end subroutine get_isc_c
496 
503  subroutine get_link_c(link_ptr, link_size) bind(C, name='get_link_f')
504  use moda_tables
505  type(c_ptr), intent(inout) :: link_ptr
506  integer(c_int), intent(out) :: link_size
507 
508  allocate(link_f(ntab))
509  link_f(1:ntab) = link(1:ntab)
510  link_size = size(link_f)
511  link_ptr = c_loc(link_f(1))
512  end subroutine get_link_c
513 
520  subroutine get_itp_c(itp_ptr, itp_size) bind(C, name='get_itp_f')
521  use moda_tables
522  type(c_ptr), intent(inout) :: itp_ptr
523  integer(c_int), intent(out) :: itp_size
524 
525  allocate(itp_f(ntab))
526  itp_f(1:ntab) = itp(1:ntab)
527  itp_size = size(itp_f)
528  itp_ptr = c_loc(itp_f(1))
529  end subroutine get_itp_c
530 
538  subroutine get_typ_c(typ_ptr, typ_len, mem_size) bind(C, name='get_typ_f')
539  use moda_tables
540  type(c_ptr), intent(inout) :: typ_ptr
541  integer(c_int), intent(out) :: typ_len
542  integer(c_int), intent(out) :: mem_size
543 
544  allocate(typ_f(ntab))
545  typ_f(1:ntab) = typ(1:ntab)
546  typ_len = len(typ(1))
547  mem_size = size(typ_f)
548  typ_ptr = c_loc(typ_f(1))
549  end subroutine get_typ_c
550 
558  subroutine get_tag_c(tag_ptr, tag_len, mem_size) bind(C, name='get_tag_f')
559  use moda_tables
560  type(c_ptr), intent(inout) :: tag_ptr
561  integer(c_int), intent(out) :: tag_len
562  integer(c_int), intent(out) :: mem_size
563 
564  allocate(tag_f(ntab))
565  tag_f(1:ntab) = tag(1:ntab)
566  tag_len = len(tag(1))
567  mem_size = size(tag_f)
568  tag_ptr = c_loc(tag_f(1))
569  end subroutine get_tag_c
570 
577  subroutine get_jmpb_c(jmpb_ptr, jmpb_size) bind(C, name='get_jmpb_f')
578  use moda_tables
579  type(c_ptr), intent(inout) :: jmpb_ptr
580  integer(c_int), intent(out) :: jmpb_size
581 
582  allocate(jmpb_f(ntab))
583  jmpb_f(1:ntab) = jmpb(1:ntab)
584  jmpb_size = size(jmpb_f)
585  jmpb_ptr = c_loc(jmpb_f(1))
586  end subroutine get_jmpb_c
587 
594  subroutine get_irf_c(irf_ptr, irf_size) bind(C, name='get_irf_f')
595  use moda_tables
596  type(c_ptr), intent(inout) :: irf_ptr
597  integer(c_int), intent(out) :: irf_size
598 
599  allocate(irf_f(ntab))
600  irf_f(1:ntab) = irf(1:ntab)
601  irf_size = size(irf_f)
602  irf_ptr = c_loc(irf_f(1))
603  end subroutine get_irf_c
604 
611  subroutine get_inode_c(lun, start_node) bind(C, name='get_inode_f')
612  use moda_msgcwd
613  integer(c_int), value, intent(in) :: lun
614  integer(c_int), intent(out) :: start_node
615 
616  start_node = inode(lun)
617  end subroutine get_inode_c
618 
625  subroutine get_nval_c(lun, num_nodes) bind(C, name='get_nval_f')
626  use moda_usrint
627  integer(c_int), value, intent(in) :: lun
628  integer(c_int), intent(out) :: num_nodes
629 
630  num_nodes = nval(lun)
631  end subroutine get_nval_c
632 
640  subroutine get_val_c(lun, val_ptr, val_size) bind(C, name='get_val_f')
641  use moda_usrint
642  integer(c_int), value, intent(in) :: lun
643  type(c_ptr), intent(inout) :: val_ptr
644  integer(c_int), intent(out) :: val_size
645 
646  val_size = size(val(:, lun))
647  val_ptr = c_loc(val(1, lun))
648  end subroutine get_val_c
649 
657  subroutine get_inv_c(lun, inv_ptr, inv_size) bind(C, name='get_inv_f')
658  use moda_usrint
659  integer(c_int), value, intent(in) :: lun
660  type(c_ptr), intent(inout) :: inv_ptr
661  integer(c_int), intent(out) :: inv_size
662 
663  inv_size = size(inv(:, lun))
664  inv_ptr = c_loc(inv(1, lun))
665  end subroutine get_inv_c
666 
676  subroutine readlc_c(lunit, str_id, output_str, output_str_len) bind(C, name='readlc_f')
677  use moda_rlccmn
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
684 
685  lstr = get_c_string_length(str_id)
686  str = transfer(str_id(1:lstr), str)
687 
688  call readlc(lunit, output_str_f, str(1:lstr))
689 
690  output_str_len_f = len(trim(output_str_f)) + 1 ! add 1 for the null terminator
691  call copy_f_c_str(output_str_f, output_str, min(output_str_len_f, output_str_len))
692  end subroutine readlc_c
693 
697  subroutine delete_table_data_c() bind(C, name='delete_table_data_f')
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)
705  end subroutine delete_table_data_c
706 
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
723  integer :: iupbs01, ltag
724  character(len=10) :: tag
725 
726  ltag = get_c_string_length(mnemonic)
727  tag = transfer(mnemonic(1:ltag), tag)
728 
729  ires = iupbs01(bufr,tag(1:ltag))
730  end function iupbs01_c
731 
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
745  integer :: igetprm
746 
747  ires = igetprm(c_f_string(cprmnm))
748  end function igetprm_c
749 
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
764  integer :: isetprm
765 
766  ires = isetprm(c_f_string(cprmnm),ipval)
767  end function isetprm_c
768 
777  subroutine maxout_c(max0) bind(C, name='maxout_f')
778  integer(c_int), value, intent(in) :: max0
779 
780  call maxout(max0)
781  end subroutine maxout_c
782 
792  function igetmxby_c() result(ires) bind(C, name='igetmxby_f')
793  integer(c_int) :: ires
794  integer :: igetmxby
795 
796  ires = igetmxby()
797  end function igetmxby_c
798 
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
813 
814  call cadn30(idn, adn_f)
815  call copy_f_c_str(adn_f, adn, adn_str_len)
816  end subroutine cadn30_c
817 
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
832  integer :: igetntbi
833  character(len=1) :: table_type_f
834 
835  table_type_f(1:1) = table_type(1)(1:1)
836 
837  ires = igetntbi(lun, table_type_f)
838  end function igetntbi_c
839 
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
853  integer :: ii
854 
855  do ii = 1,80
856  card_f(ii:ii) = card(ii)
857  enddo
858  call elemdx(card_f, lun)
859  end subroutine elemdx_c
860 
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
877 
878  character(len=9) :: nemo_f
879  character(len=1) :: tab_f
880 
881  call numtbd(lun, idn, nemo_f, tab_f, iret)
882 
883  call copy_f_c_str(nemo_f, nemo, nemo_str_len)
884  tab(1) = tab_f(1:1)
885  end subroutine numtbd_c
886 
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
900  integer :: ifxy
901 
902  ires = ifxy(c_f_string(cfxy))
903  end function ifxy_c
904 
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
924 
925  call uptdd(id, lun, ient, iret)
926  end subroutine uptdd_c
927 
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
940  integer :: imrkopr
941 
942  ires = imrkopr(c_f_string(nemo))
943  end function imrkopr_c
944 
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
957  integer :: istdesc
958 
959  ires = istdesc(idn)
960  end function istdesc_c
961 
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
980  integer :: lstr
981 
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))
986  end subroutine ufbseq_c
987 
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
1009  integer :: ireadns
1010 
1011  ires = ireadns(bufr_unit, f_subset, iddate)
1012 
1013  if (ires == 0) then
1014  call copy_f_c_str(f_subset, c_subset, subset_str_len)
1015  end if
1016  end function ireadns_c
1017 
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
1037 
1038  call readns(bufr_unit, f_subset, iddate, ires)
1039 
1040  if (ires == 0) then
1041  call copy_f_c_str(f_subset, c_subset, subset_str_len)
1042  end if
1043  end subroutine readns_c
1044 
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
1057  integer :: ibfms
1058 
1059  ires = ibfms(r8val)
1060  end function ibfms_c
1061 
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
1074 
1075  call strnum(c_f_string(str), num, iret)
1076  end subroutine strnum_c
1077 
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
1095  integer :: ii
1096 
1097  do ii = 1,6
1098  numb_f(ii:ii) = numb(ii)
1099  enddo
1100  do ii = 1,8
1101  nemo_f(ii:ii) = nemo(ii)
1102  enddo
1103  do ii = 1,55
1104  celsq_f(ii:ii) = celsq(ii)
1105  enddo
1106  call stntbi(n, lun, numb_f, nemo_f, celsq_f)
1107  end subroutine stntbi_c
1108 
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
1122  integer :: igettdi
1123 
1124  ires = igettdi(iflag)
1125  end function igettdi_c
1126 
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
1142 
1143  call pktdd(id, lun, idn, iret)
1144  end subroutine pktdd_c
1145 
1153  subroutine bort_c(errstr) bind(C, name='bort_f')
1154  character(kind=c_char), intent(in) :: errstr(*)
1155 
1156  call bort(c_f_string(errstr))
1157  end subroutine bort_c
1158 
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
1173  integer :: lfs
1174 
1175  lfs = get_c_string_length(c_subset)
1176  f_subset = transfer(c_subset(1:lfs), f_subset)
1177 
1178  call openmb(bufr_unit, f_subset(1:lfs), iddate)
1179  end subroutine openmb_c
1180 
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
1193 
1194  call bvers(f_cverstr)
1195  call copy_f_c_str(f_cverstr, cverstr, cverstr_len)
1196  end subroutine bvers_c
1197 
1206  subroutine cmpmsg_c(cf) bind(C, name='cmpmsg_f')
1207  character(kind=c_char), intent(in) :: cf(*)
1208  character :: ch
1209 
1210  ch = cf(1)
1211  call cmpmsg(ch)
1212  end subroutine cmpmsg_c
1213 
1214 end module bufr_c2f_interface
integer function igetprm(cprmnm)
Return the current value of a parameter used for allocating one or more internal arrays within the NC...
Definition: arallocf.F90:1125
subroutine exitbufr
Free all dynamically-allocated memory, close all logical units that are open within the NCEPLIBS-bufr...
Definition: arallocf.F90:899
recursive integer function isetprm(cprmnm, ipval)
Set a specified parameter to a specified value for use in dynamically allocating one or more internal...
Definition: arallocf.F90:993
integer function imrkopr(nemo)
Check whether a specified mnemonic is a Table C marker operator.
Definition: bitmaps.F90:361
recursive subroutine bort(str)
Log an error message, then either return to or abort the application program.
Definition: borts.F90:15
subroutine cmpmsg(cf)
Specify whether BUFR messages output by future calls to message-writing subroutines and subset-writin...
Definition: compress.F90:33
subroutine elemdx(card, lun)
Decode the scale factor, reference value, bit width and units (i.e., the "elements") from a Table B m...
Definition: dxtable.F90:514
subroutine nemtbb(lun, itab, unit, iscl, iref, ibit)
Get information about a Table B descriptor from the internal DX BUFR tables.
Definition: dxtable.F90:1267
subroutine stntbi(n, lun, numb, nemo, celsq)
Store a new entry within internal BUFR Table B or D.
Definition: dxtable.F90:1610
subroutine pktdd(id, lun, idn, iret)
Store information about a child mnemonic within the internal BUFR Table D.
Definition: dxtable.F90:1655
recursive subroutine nemdefs(lunit, nemo, celem, cunit, iret)
Get the element name and units associated with a Table B descriptor.
Definition: dxtable.F90:1435
integer function igetntbi(lun, ctb)
Get the next available index for storing an entry within a specified internal DX BUFR table.
Definition: dxtable.F90:1142
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...
Definition: dxtable.F90:1729
subroutine nemtab(lun, nemo, idn, tab, iret)
Get information about a descriptor, based on a mnemonic.
Definition: fxy.F90:434
subroutine cadn30(idn, adn)
Convert an FXY value from its WMO bit-wise representation to its 6 character representation.
Definition: fxy.F90:65
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...
Definition: fxy.F90:290
integer function ifxy(adsc)
Convert an FXY value from its 6 character representation to its WMO bit-wise representation.
Definition: fxy.F90:152
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...
Definition: mastertable.F90:35
subroutine bvers(cverstr)
Get the version number of the NCEPLIBS-bufr software.
Definition: misc.F90:361
recursive subroutine strnum(str, num, iret)
Decode an integer from a character string.
Definition: misc.F90:156
integer function ibfms(r8val)
Check whether a real*8 data value returned from a previous call to any of the NCEPLIBS-bufr values-re...
Definition: missing.F90:25
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.
Definition: readwritemg.F90:44
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.
Definition: readwritesb.F90:32
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.
Definition: s013vals.F90:247
integer function istdesc(idn)
Given the WMO bit-wise representation of an FXY value for a descriptor, check whether the descriptor ...
Definition: standard.F90:299