ROMS
Loading...
Searching...
No Matches
mod_pio_netcdf::pio_netcdf_get_svar Interface Reference

Public Member Functions

subroutine pio_netcdf_get_svar_0d (ng, model, ncname, myvarname, a, piofile, start, total)
 
subroutine pio_netcdf_get_svar_1d (ng, model, ncname, myvarname, a, piofile, start, total)
 
subroutine pio_netcdf_get_svar_2d (ng, model, ncname, myvarname, a, piofile, start, total)
 
subroutine pio_netcdf_get_svar_3d (ng, model, ncname, myvarname, a, piofile, start, total)
 

Detailed Description

Definition at line 77 of file mod_pio_netcdf.F.

Member Function/Subroutine Documentation

◆ pio_netcdf_get_svar_0d()

subroutine mod_pio_netcdf::pio_netcdf_get_svar::pio_netcdf_get_svar_0d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
character (len=*), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total )

Definition at line 5483 of file mod_pio_netcdf.F.

5485!
5486!=======================================================================
5487! !
5488! This routine reads requested string scalar variable from specified !
5489! NetCDF file. The CDL of the scalar variable has one-dimension in !
5490! the NetCDF file for the number of characters: !
5491! !
5492! char string(Nchars) CDL !
5493! !
5494! character (len=Nchars) :: string F90 !
5495! !
5496! to read a scalar string use: !
5497! !
5498! start = (/1/) !
5499! total = (/Nchars/) !
5500! !
5501! On Input: !
5502! !
5503! ng Nested grid number (integer) !
5504! model Calling model identifier (integer) !
5505! ncname NetCDF file name (string) !
5506! myVarName Variable name (string) !
5507! ncid NetCDF file ID (integer, OPTIONAL) !
5508! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
5509! pioFile%fh file handler !
5510! pioFile%iosystem IO system descriptor (struct) !
5511! total Number of data values to be read along each !
5512! dimension (integer, OPTIONAL) !
5513! !
5514! On Ouput: !
5515! !
5516! A Read scalar variable (string) !
5517! !
5518! Examples: !
5519! !
5520! CALL netcdf_get_svar (ng, iNLM, 'file.nc', 'VarName', ivar) !
5521! CALL netcdf_get_svar (ng, iNLM, 'file.nc', 'VarName', ivar(1)) !
5522! !
5523!=======================================================================
5524!
5525! Imported variable declarations.
5526!
5527 integer, intent(in) :: ng, model
5528
5529 integer, intent(in), optional :: start(:)
5530 integer, intent(in), optional :: total(:)
5531!
5532 character (len=*), intent(in) :: ncname
5533 character (len=*), intent(in) :: myVarName
5534
5535 character (len=*), intent(out) :: A
5536!
5537 TYPE (File_desc_t), intent(in), optional :: pioFile
5538!
5539! Local variable declarations.
5540!
5541 integer :: status
5542!
5543 character (len=LEN(A)), dimension(1) :: my_A
5544
5545 character (len=*), parameter :: MyFile = &
5546 & __FILE__//", pio_netcdf_get_svar_0d"
5547!
5548 TYPE (File_desc_t) :: my_pioFile
5549 TYPE (Var_desc_t) :: my_pioVar
5550!
5551!-----------------------------------------------------------------------
5552! Read in a string scalar variable.
5553!-----------------------------------------------------------------------
5554!
5555! If NetCDF file ID is not provided, open NetCDF for reading.
5556!
5557 IF (.not.PRESENT(piofile)) THEN
5558 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
5559 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
5560 ELSE
5561 my_piofile=piofile
5562 END IF
5563!
5564! Read in variable.
5565!
5566 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
5567 IF (status.eq.pio_noerr) THEN
5568 IF (PRESENT(start).and.PRESENT(total)) THEN
5569 status=pio_get_var(my_piofile, my_piovar, start, total, my_a)
5570 a=my_a(1)
5571 ELSE
5572 status=pio_get_var(my_piofile, my_piovar, a)
5573 END IF
5574 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
5575 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
5576 & trim(sourcefile)
5577 exit_flag=2
5578 ioerror=status
5579 END IF
5580 ELSE
5581 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
5582 & trim(sourcefile)
5583 exit_flag=2
5584 ioerror=status
5585 END IF
5586!
5587! If NetCDF file ID is not provided, close input NetCDF file.
5588!
5589 IF (.not.PRESENT(piofile)) THEN
5590 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
5591 END IF
5592!
5593 10 FORMAT (/,' PIO_NETCDF_GET_SVAR_0D - error while reading ', &
5594 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
5595 & /,26x,'call from:',2x,a)
5596 20 FORMAT (/,' pio_NETCDF_GET_SVAR_0D - error while inquiring ', &
5597 & 'descriptor for variable:',2x,a, &
5598 & /,26x,'in input file:',2x,a,/,26x,'call from:',2x,a)
5599!
5600 RETURN

References mod_scalars::exit_flag, strings_mod::founderror(), mod_iounits::ioerror, mod_parallel::master, mod_scalars::noerror, mod_pio_netcdf::pio_netcdf_close(), mod_pio_netcdf::pio_netcdf_open(), mod_iounits::sourcefile, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_svar_1d()

subroutine mod_pio_netcdf::pio_netcdf_get_svar::pio_netcdf_get_svar_1d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
character (len=*), dimension(:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total )

Definition at line 5603 of file mod_pio_netcdf.F.

5605!
5606!=======================================================================
5607! !
5608! This routine reads requested string 1D-array variable or array !
5609! element from specified NetCDF file. The CDL of the 1D-array !
5610! variable has two-dimensions in the NetCDF file, and the first !
5611! dimension is the number of characters: !
5612! !
5613! char string(dim1, Nchars) CDL !
5614! !
5615! character (len=Nchars) :: string(dim1) F90 !
5616! !
5617! to read a single array element at location (i) use: !
5618! !
5619! start = (/1, i/) !
5620! total = (/Nchars, 1/) !
5621! !
5622! On Input: !
5623! !
5624! ng Nested grid number (integer) !
5625! model Calling model identifier (integer) !
5626! ncname NetCDF file name (string) !
5627! myVarName Variable name (string) !
5628! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
5629! pioFile%fh file handler !
5630! pioFile%iosystem IO system descriptor (struct) !
5631! start Starting index where the first of the data values !
5632! will be read along each dimension (integer, !
5633! OPTIONAL) !
5634! total Number of data values to be read along each !
5635! dimension (integer, OPTIONAL) !
5636! !
5637! On Ouput: !
5638! !
5639! A Read 1D-array variable or array element (string) !
5640! !
5641!=======================================================================
5642!
5643! Imported variable declarations.
5644!
5645 integer, intent(in) :: ng, model
5646
5647 integer, intent(in), optional :: start(:)
5648 integer, intent(in), optional :: total(:)
5649!
5650 character (len=*), intent(in) :: ncname
5651 character (len=*), intent(in) :: myVarName
5652
5653 character (len=*), intent(out) :: A(:)
5654!
5655 TYPE (File_desc_t), intent(in), optional :: pioFile
5656!
5657! Local variable declarations.
5658!
5659 integer :: status
5660!
5661 character (len=*), parameter :: MyFile = &
5662 & __FILE__//", pio_netcdf_get_svar_1d"
5663!
5664 TYPE (File_desc_t) :: my_pioFile
5665 TYPE (Var_desc_t) :: my_pioVar
5666!
5667!-----------------------------------------------------------------------
5668! Read in a string 1D-array or array element.
5669!-----------------------------------------------------------------------
5670!
5671! If NetCDF file ID is not provided, open NetCDF for reading.
5672!
5673 IF (.not.PRESENT(piofile)) THEN
5674 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
5675 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
5676 ELSE
5677 my_piofile=piofile
5678 END IF
5679!
5680! Read in variable.
5681!
5682 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
5683 IF (status.eq.pio_noerr) THEN
5684 IF (PRESENT(start).and.PRESENT(total)) THEN
5685 status=pio_get_var(my_piofile, my_piovar, start, total, a)
5686 ELSE
5687 status=pio_get_var(my_piofile, my_piovar, a)
5688 END IF
5689 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
5690 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
5691 & trim(sourcefile)
5692 exit_flag=2
5693 ioerror=status
5694 END IF
5695 ELSE
5696 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
5697 & trim(sourcefile)
5698 exit_flag=2
5699 ioerror=status
5700 END IF
5701!
5702! If NetCDF file ID is not provided, close input NetCDF file.
5703!
5704 IF (.not.PRESENT(piofile)) THEN
5705 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
5706 END IF
5707!
5708 10 FORMAT (/,' PIO_NETCDF_GET_SVAR_1D - error while reading ', &
5709 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
5710 & /,26x,'call from:',2x,a)
5711 20 FORMAT (/,' pio_NETCDF_GET_SVAR_1D - error while inquiring ', &
5712 & 'descriptor for variable:',2x,a, &
5713 & /,26x,'in input file:',2x,a,/,26x,'call from:',2x,a)
5714!
5715 RETURN

References mod_scalars::exit_flag, strings_mod::founderror(), mod_iounits::ioerror, mod_parallel::master, mod_scalars::noerror, mod_pio_netcdf::pio_netcdf_close(), mod_pio_netcdf::pio_netcdf_open(), mod_iounits::sourcefile, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_svar_2d()

subroutine mod_pio_netcdf::pio_netcdf_get_svar::pio_netcdf_get_svar_2d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
character (len=*), dimension(:,:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total )

Definition at line 5718 of file mod_pio_netcdf.F.

5720!
5721!=======================================================================
5722! !
5723! This routine reads requested string 2D-array variable or array !
5724! element from specified NetCDF file. The CDL of the 1D-array !
5725! variable has three-dimensions in the NetCDF file, and the first !
5726! dimension is the number of characters: !
5727! !
5728! char string(dim2, dim1, Nchars) CDL !
5729! !
5730! character (len=Nchars) :: string(dim1, dim2) F90 !
5731! !
5732! to read a single array element at location (i,j) use: !
5733! !
5734! start = (/1, i, j/) !
5735! total = (/Nchars, 1, 1/) !
5736! !
5737! On Input: !
5738! !
5739! ng Nested grid number (integer) !
5740! model Calling model identifier (integer) !
5741! ncname NetCDF file name (string) !
5742! myVarName Variable name (string) !
5743! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
5744! pioFile%fh file handler !
5745! pioFile%iosystem IO system descriptor (struct) !
5746! start Starting index where the first of the data values !
5747! will be read along each dimension (integer, !
5748! OPTIONAL) !
5749! total Number of data values to be read along each !
5750! dimension (integer, OPTIONAL) !
5751! !
5752! On Ouput: !
5753! !
5754! A Read 2D-array variable or array element (string) !
5755! !
5756!=======================================================================
5757!
5758! Imported variable declarations.
5759!
5760 integer, intent(in) :: ng, model
5761
5762 integer, intent(in), optional :: start(:)
5763 integer, intent(in), optional :: total(:)
5764!
5765 character (len=*), intent(in) :: ncname
5766 character (len=*), intent(in) :: myVarName
5767
5768 character (len=*), intent(out) :: A(:,:)
5769!
5770 TYPE (File_desc_t), intent(in), optional :: pioFile
5771!
5772! Local variable declarations.
5773!
5774 integer :: status
5775!
5776 character (len=*), parameter :: MyFile = &
5777 & __FILE__//", pio_netcdf_get_svar_2d"
5778!
5779 TYPE (File_desc_t) :: my_pioFile
5780 TYPE (Var_desc_t) :: my_pioVar
5781!
5782!-----------------------------------------------------------------------
5783! Read in a string 2D-array or array element.
5784!-----------------------------------------------------------------------
5785!
5786! If NetCDF file ID is not provided, open NetCDF for reading.
5787!
5788 IF (.not.PRESENT(piofile)) THEN
5789 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
5790 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
5791 ELSE
5792 my_piofile=piofile
5793 END IF
5794!
5795! Read in variable.
5796!
5797 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
5798 IF (status.eq.pio_noerr) THEN
5799 IF (PRESENT(start).and.PRESENT(total)) THEN
5800 status=pio_get_var(my_piofile, my_piovar, start, total, a)
5801 ELSE
5802 status=pio_get_var(my_piofile, my_piovar, a)
5803 END IF
5804 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
5805 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
5806 & trim(sourcefile)
5807 exit_flag=2
5808 ioerror=status
5809 END IF
5810 ELSE
5811 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
5812 & trim(sourcefile)
5813 exit_flag=2
5814 ioerror=status
5815 END IF
5816!
5817! If NetCDF file ID is not provided, close input NetCDF file.
5818!
5819 IF (.not.PRESENT(piofile)) THEN
5820 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
5821 END IF
5822!
5823 10 FORMAT (/,' PIO_NETCDF_GET_SVAR_2D - error while reading ', &
5824 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
5825 & /,26x,'call from:',2x,a)
5826 20 FORMAT (/,' pio_NETCDF_GET_SVAR_2D - error while inquiring ', &
5827 & 'descriptor for variable:',2x,a, &
5828 & /,26x,'in input file:',2x,a,/,26x,'call from:',2x,a)
5829!
5830 RETURN

References mod_scalars::exit_flag, strings_mod::founderror(), mod_iounits::ioerror, mod_parallel::master, mod_scalars::noerror, mod_pio_netcdf::pio_netcdf_close(), mod_pio_netcdf::pio_netcdf_open(), mod_iounits::sourcefile, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_svar_3d()

subroutine mod_pio_netcdf::pio_netcdf_get_svar::pio_netcdf_get_svar_3d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
character (len=*), dimension(:,:,:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total )

Definition at line 5833 of file mod_pio_netcdf.F.

5835!
5836!=======================================================================
5837! !
5838! This routine reads requested string 3D-array variable or array !
5839! element from specified NetCDF file. The CDL of the 1D-array !
5840! variable has four-dimensions in the NetCDF file, and the first !
5841! dimension is the number of characters: !
5842! !
5843! char string(dim3, dim2, dim1, Nchars) CDL !
5844! !
5845! character (len=Nchars) :: string(dim1, dim2, dim3) F90 !
5846! !
5847! to read a single array element at location (i,j,k) use: !
5848! !
5849! start = (/1, i, j, k/) !
5850! total = (/Nchars, 1, 1, 1/) !
5851! !
5852! On Input: !
5853! !
5854! ng Nested grid number (integer) !
5855! model Calling model identifier (integer) !
5856! ncname NetCDF file name (string) !
5857! myVarName Variable name (string) !
5858! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
5859! pioFile%fh file handler !
5860! pioFile%iosystem IO system descriptor (struct) !
5861! start Starting index where the first of the data values !
5862! will be read along each dimension (integer, !
5863! OPTIONAL) !
5864! total Number of data values to be read along each !
5865! dimension (integer, OPTIONAL) !
5866! !
5867! On Ouput: !
5868! !
5869! A Read 3D-array variable or array element (string) !
5870! !
5871!=======================================================================
5872!
5873! Imported variable declarations.
5874!
5875 integer, intent(in) :: ng, model
5876
5877 integer, intent(in), optional :: start(:)
5878 integer, intent(in), optional :: total(:)
5879!
5880 character (len=*), intent(in) :: ncname
5881 character (len=*), intent(in) :: myVarName
5882
5883 character (len=*), intent(out) :: A(:,:,:)
5884!
5885 TYPE (File_desc_t), intent(in), optional :: pioFile
5886!
5887! Local variable declarations.
5888!
5889 integer :: status
5890!
5891 character (len=*), parameter :: MyFile = &
5892 & __FILE__//", pio_netcdf_get_svar_3d"
5893!
5894 TYPE (File_desc_t) :: my_pioFile
5895 TYPE (Var_desc_t) :: my_pioVar
5896!
5897!-----------------------------------------------------------------------
5898! Read in a string 3D-array or array element.
5899!-----------------------------------------------------------------------
5900!
5901! If NetCDF file ID is not provided, open NetCDF for reading.
5902!
5903 IF (.not.PRESENT(piofile)) THEN
5904 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
5905 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
5906 ELSE
5907 my_piofile=piofile
5908 END IF
5909!
5910! Read in variable.
5911!
5912 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
5913 IF (status.eq.pio_noerr) THEN
5914 IF (PRESENT(start).and.PRESENT(total)) THEN
5915 status=pio_get_var(my_piofile, my_piovar, start, total, a)
5916 ELSE
5917 status=pio_get_var(my_piofile, my_piovar, a)
5918 END IF
5919 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
5920 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
5921 & trim(sourcefile)
5922 exit_flag=2
5923 ioerror=status
5924 END IF
5925 ELSE
5926 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
5927 & trim(sourcefile)
5928 exit_flag=2
5929 ioerror=status
5930 END IF
5931!
5932! If NetCDF file ID is not provided, close input NetCDF file.
5933!
5934 IF (.not.PRESENT(piofile)) THEN
5935 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
5936 END IF
5937!
5938 10 FORMAT (/,' PIO_NETCDF_GET_SVAR_3D - error while reading ', &
5939 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
5940 & /,26x,'call from:',2x,a)
5941 20 FORMAT (/,' pio_NETCDF_GET_SVAR_3D - error while inquiring ', &
5942 & 'descriptor for variable:',2x,a, &
5943 & /,26x,'in input file:',2x,a,/,26x,'call from:',2x,a)
5944!
5945 RETURN

References mod_scalars::exit_flag, strings_mod::founderror(), mod_iounits::ioerror, mod_parallel::master, mod_scalars::noerror, mod_pio_netcdf::pio_netcdf_close(), mod_pio_netcdf::pio_netcdf_open(), mod_iounits::sourcefile, and mod_iounits::stdout.

Here is the call graph for this function:

The documentation for this interface was generated from the following file: