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

Public Member Functions

subroutine pio_netcdf_get_fvar_0dp (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_1dp (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_2dp (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_3dp (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_0d (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_1d (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_2d (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_3d (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 
subroutine pio_netcdf_get_fvar_4d (ng, model, ncname, myvarname, a, piofile, start, total, broadcast, min_val, max_val)
 

Detailed Description

Definition at line 52 of file mod_pio_netcdf.F.

Member Function/Subroutine Documentation

◆ pio_netcdf_get_fvar_0d()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_0d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(r8), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(r8), intent(out), optional min_val,
real(r8), intent(out), optional max_val )

Definition at line 3813 of file mod_pio_netcdf.F.

3816!
3817!=======================================================================
3818! !
3819! This routine reads requested floating-point scalar variable from !
3820! specified NetCDF file. !
3821! !
3822! On Input: !
3823! !
3824! ng Nested grid number (integer) !
3825! model Calling model identifier (integer) !
3826! ncname NetCDF file name (string) !
3827! myVarName Variable name (string) !
3828! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
3829! pioFile%fh file handler !
3830! pioFile%iosystem IO system descriptor (struct) !
3831! start Starting index where the first of the data values !
3832! will be read along each dimension (integer, !
3833! OPTIONAL) !
3834! total Number of data values to be read along each !
3835! dimension (integer, OPTIONAL) !
3836! broadcast Switch to broadcast read values from root to all !
3837! members of the communicator in distributed- !
3838! memory applications (logical, OPTIONAL). It is !
3839! ignored since PIO library broadcasts the values !
3840! to all member in the group by default. !
3841! !
3842! On Ouput: !
3843! !
3844! A Read scalar variable (real) !
3845! min_val Read data minimum value (real, OPTIONAL) !
3846! max_val Read data maximum value (real, OPTIONAL) !
3847! !
3848! Examples: !
3849! !
3850! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
3851! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(1)) !
3852! !
3853!=======================================================================
3854!
3855! Imported variable declarations.
3856!
3857 logical, intent(in), optional :: broadcast
3858!
3859 integer, intent(in) :: ng, model
3860
3861 integer, intent(in), optional :: start(:)
3862 integer, intent(in), optional :: total(:)
3863!
3864 character (len=*), intent(in) :: ncname
3865 character (len=*), intent(in) :: myVarName
3866!
3867 real(r8), intent(out), optional :: min_val
3868 real(r8), intent(out), optional :: max_val
3869
3870 real(r8), intent(out) :: A
3871!
3872 TYPE (File_desc_t), intent(in), optional :: pioFile
3873!
3874! Local variable declarations.
3875!
3876 integer :: status
3877!
3878 real(r8), dimension(1) :: my_A
3879!
3880 character (len=*), parameter :: MyFile = &
3881 & __FILE__//", pio_netcdf_get_fvar_0d"
3882!
3883 TYPE (File_desc_t) :: my_pioFile
3884 TYPE (Var_desc_t) :: my_pioVar
3885!
3886!-----------------------------------------------------------------------
3887! Read in a floating-point scalar variable.
3888!-----------------------------------------------------------------------
3889!
3890! If file descriptor is not provided, open NetCDF for reading.
3891!
3892 IF (.not.PRESENT(piofile)) THEN
3893 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
3894 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
3895 ELSE
3896 my_piofile=piofile
3897 END IF
3898!
3899! Read in variable.
3900!
3901 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
3902 IF (status.eq.pio_noerr) THEN
3903 IF (PRESENT(start).and.PRESENT(total)) THEN
3904 status=pio_get_var(my_piofile, my_piovar, start, total, my_a)
3905 a=my_a(1)
3906 ELSE
3907 status=pio_get_var(my_piofile, my_piovar, a)
3908 END IF
3909 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
3910 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
3911 & trim(sourcefile)
3912 exit_flag=2
3913 ioerror=status
3914 END IF
3915 ELSE
3916 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
3917 & trim(sourcefile)
3918 exit_flag=2
3919 ioerror=status
3920 END IF
3921!
3922! Compute minimum and maximum values of read variable. Notice that
3923! the same read value is assigned since a scalar variable was
3924! processed.
3925!
3926 IF (PRESENT(min_val)) THEN
3927 min_val=a
3928 END IF
3929 IF (PRESENT(max_val)) THEN
3930 max_val=a
3931 END IF
3932!
3933! If file descriptor is not provided, close input NetCDF file.
3934!
3935 IF (.not.PRESENT(piofile)) THEN
3936 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
3937 END IF
3938!
3939 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_0D - error while reading ', &
3940 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
3941 & /,26x,'call from:',2x,a)
3942 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_0D - error while inquiring ', &
3943 & 'descriptor for variable:',2x,a,/,26x,'in input file:', &
3944 & 2x,a,/,26x,'call from:',2x,a)
3945!
3946 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_fvar_0dp()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_0dp ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(dp), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(dp), intent(out), optional min_val,
real(dp), intent(out), optional max_val )

Definition at line 3017 of file mod_pio_netcdf.F.

3020!
3021!=======================================================================
3022! !
3023! This routine reads requested double-precision scalar variable from !
3024! specified NetCDF file. !
3025! !
3026! On Input: !
3027! !
3028! ng Nested grid number (integer) !
3029! model Calling model identifier (integer) !
3030! ncname NetCDF file name (string) !
3031! myVarName Variable name (string) !
3032! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
3033! pioFile%fh file handler !
3034! pioFile%iosystem IO system descriptor (struct) !
3035! start Starting index where the first of the data values !
3036! will be read along each dimension (integer, !
3037! OPTIONAL) !
3038! total Number of data values to be read along each !
3039! dimension (integer, OPTIONAL) !
3040! broadcast Switch to broadcast read values from root to all !
3041! members of the communicator in distributed- !
3042! memory applications (logical, OPTIONAL). It is !
3043! ignored since PIO library broadcasts the values !
3044! to all member in the group by default. !
3045! !
3046! On Ouput: !
3047! !
3048! A Read scalar variable (double precision) !
3049! min_val Read data minimum value (double precision, OPTIONAL)!
3050! max_val Read data maximum value (double precision, OPTIONAL)!
3051! !
3052! Examples: !
3053! !
3054! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
3055! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(1)) !
3056! !
3057!=======================================================================
3058!
3059! Imported variable declarations.
3060!
3061 logical, intent(in), optional :: broadcast
3062!
3063 integer, intent(in) :: ng, model
3064
3065 integer, intent(in), optional :: start(:)
3066 integer, intent(in), optional :: total(:)
3067!
3068 character (len=*), intent(in) :: ncname
3069 character (len=*), intent(in) :: myVarName
3070!
3071 real(dp), intent(out), optional :: min_val
3072 real(dp), intent(out), optional :: max_val
3073
3074 real(dp), intent(out) :: A
3075!
3076 TYPE (File_desc_t), intent(in), optional :: pioFile
3077!
3078! Local variable declarations.
3079!
3080 integer :: status
3081!
3082 real(dp), dimension(1) :: my_A
3083!
3084 character (len=*), parameter :: MyFile = &
3085 & __FILE__//", pio_netcdf_get_fvar_0dp"
3086!
3087 TYPE (File_desc_t) :: my_pioFile
3088 TYPE (Var_desc_t) :: my_pioVar
3089!
3090!-----------------------------------------------------------------------
3091! Read in a double-precision scalar variable.
3092!-----------------------------------------------------------------------
3093!
3094! If file descriptor is not provided, open NetCDF for reading.
3095!
3096 IF (.not.PRESENT(piofile)) THEN
3097 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
3098 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
3099 ELSE
3100 my_piofile=piofile
3101 END IF
3102!
3103! Read in variable.
3104!
3105 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
3106 IF (status.eq.pio_noerr) THEN
3107 IF (PRESENT(start).and.PRESENT(total)) THEN
3108 status=pio_get_var(my_piofile, my_piovar, start, total, my_a)
3109 a=my_a(1)
3110 ELSE
3111 status=pio_get_var(my_piofile, my_piovar, a)
3112 END IF
3113 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
3114 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
3115 & trim(sourcefile)
3116 exit_flag=2
3117 ioerror=status
3118 END IF
3119 ELSE
3120 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
3121 & trim(sourcefile)
3122 exit_flag=2
3123 ioerror=status
3124 END IF
3125!
3126! Compute minimum and maximum values of read variable. Notice that
3127! the same read value is assigned since a scalar variable was
3128! processed.
3129!
3130 IF (PRESENT(min_val)) THEN
3131 min_val=a
3132 END IF
3133 IF (PRESENT(max_val)) THEN
3134 max_val=a
3135 END IF
3136!
3137! If file descriptor is not provided, close input NetCDF file.
3138!
3139 IF (.not.PRESENT(piofile)) THEN
3140 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
3141 END IF
3142!
3143 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_0DP - error while reading ', &
3144 & 'variable:',2x,a,/,27x,'in input file:',2x,a, &
3145 & /,27x,'call from:',2x,a)
3146 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_0DP - error while inquiring ', &
3147 & 'descriptor for variable:',2x,a,/,27x,'in input file:', &
3148 & 2x,a,/,27x,'call from:',2x,a)
3149!
3150 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_fvar_1d()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_1d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(r8), dimension(:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(r8), intent(out), optional min_val,
real(r8), intent(out), optional max_val )

Definition at line 3949 of file mod_pio_netcdf.F.

3952!
3953!=======================================================================
3954! !
3955! This routine reads requested floating-point 1D-array variable from !
3956! specified NetCDF file. !
3957! !
3958! On Input: !
3959! !
3960! ng Nested grid number (integer) !
3961! model Calling model identifier (integer) !
3962! ncname NetCDF file name (string) !
3963! myVarName Variable name (string) !
3964! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
3965! pioFile%fh file handler !
3966! pioFile%iosystem IO system descriptor (struct) !
3967! start Starting index where the first of the data values !
3968! will be read along each dimension (integer, !
3969! OPTIONAL) !
3970! total Number of data values to be read along each !
3971! dimension (integer, OPTIONAL) !
3972! !
3973! broadcast Switch to broadcast read values from root to all !
3974! members of the communicator in distributed- !
3975! memory applications (logical, OPTIONAL). It is !
3976! ignored since PIO library broadcasts the values !
3977! to all member in the group by default. !
3978! !
3979! On Ouput: !
3980! !
3981! A Read 1D-array variable (real) !
3982! min_val Read data minimum value (real, OPTIONAL) !
3983! max_val Read data maximum value (real, OPTIONAL) !
3984! !
3985! Examples: !
3986! !
3987! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
3988! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(0:)) !
3989! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(:,1)) !
3990! !
3991!=======================================================================
3992!
3993! Imported variable declarations.
3994!
3995 logical, intent(in), optional :: broadcast
3996!
3997 integer, intent(in) :: ng, model
3998
3999 integer, intent(in), optional :: start(:)
4000 integer, intent(in), optional :: total(:)
4001!
4002 character (len=*), intent(in) :: ncname
4003 character (len=*), intent(in) :: myVarName
4004!
4005 real(r8), intent(out), optional :: min_val
4006 real(r8), intent(out), optional :: max_val
4007
4008 real(r8), intent(out) :: A(:)
4009!
4010 TYPE (File_desc_t), intent(in), optional :: pioFile
4011!
4012! Local variable declarations.
4013!
4014 logical, dimension(3) :: foundit
4015!
4016 integer :: i, status
4017
4018 integer, dimension(1) :: Asize
4019!
4020 real(r8) :: Afactor, Aoffset, Aspval
4021
4022 real(r8), parameter :: Aepsilon = 1.0e-8_r8
4023
4024 real(r8), dimension(3) :: AttValue
4025!
4026 character (len=12), dimension(3) :: AttName
4027
4028 character (len=*), parameter :: MyFile = &
4029 & __FILE__//", pio_netcdf_get_fvar_1d"
4030!
4031 TYPE (File_desc_t) :: my_pioFile
4032 TYPE (Var_desc_t) :: my_pioVar
4033!
4034!-----------------------------------------------------------------------
4035! Read in a floating-point 1D-array variable.
4036!-----------------------------------------------------------------------
4037!
4038 IF (PRESENT(start).and.PRESENT(total)) THEN
4039 asize(1)=1
4040 DO i=1,SIZE(total) ! this logic is for the case
4041 asize(1)=asize(1)*total(i) ! of reading multidimensional
4042 END DO ! data into a compact 1D array
4043 ELSE
4044 asize(1)=ubound(a, dim=1)
4045 END IF
4046!
4047! If file descriptor is not provided, open NetCDF for reading.
4048!
4049 IF (.not.PRESENT(piofile)) THEN
4050 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
4051 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
4052 ELSE
4053 my_piofile=piofile
4054 END IF
4055!
4056! Read in variable.
4057!
4058 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
4059 IF (status.eq.pio_noerr) THEN
4060 IF (PRESENT(start).and.PRESENT(total)) THEN
4061 status=pio_get_var(my_piofile, my_piovar, start, total, a)
4062 ELSE
4063 status=pio_get_var(my_piofile, my_piovar, a)
4064 END IF
4065 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
4066 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
4067 & trim(sourcefile)
4068 exit_flag=2
4069 ioerror=status
4070 END IF
4071 ELSE
4072 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
4073 & trim(sourcefile)
4074 exit_flag=2
4075 ioerror=status
4076 END IF
4077!
4078! Check if the following attributes: "scale_factor", "add_offset", and
4079! "_FillValue" are present in the input NetCDF variable:
4080!
4081! If the "scale_value" attribute is present, the data is multiplied by
4082! this factor after reading.
4083! If the "add_offset" attribute is present, this value is added to the
4084! data after reading.
4085! If both "scale_factor" and "add_offset" attributes are present, the
4086! data are first scaled before the offset is added.
4087! If the "_FillValue" attribute is present, the data having this value
4088! is treated as missing and it is replaced with zero. This feature it
4089! is usually related with the land/sea masking.
4090!
4091 attname(1)='scale_factor'
4092 attname(2)='add_offset '
4093 attname(3)='_FillValue '
4094
4095 CALL pio_netcdf_get_fatt (ng, model, ncname, my_piovar, &
4096 & attname, attvalue, foundit, &
4097 & piofile = my_piofile)
4098
4099 IF (exit_flag.eq.noerror) THEN
4100 IF (.not.foundit(1)) THEN
4101 afactor=1.0_r8
4102 ELSE
4103 afactor=attvalue(1)
4104 END IF
4105
4106 IF (.not.foundit(2)) THEN
4107 aoffset=0.0_r8
4108 ELSE
4109 aoffset=attvalue(2)
4110 END IF
4111
4112 IF (.not.foundit(3)) THEN
4113 aspval=spval_check
4114 ELSE
4115 aspval=attvalue(3)
4116 END IF
4117
4118 DO i=1,asize(1) ! zero out missing values
4119 IF ((foundit(3).and.(abs(a(i)-aspval).lt.aepsilon)).or. &
4120 & (.not.foundit(3).and.(abs(a(i)).ge.abs(aspval)))) THEN
4121 a(i)=0.0_r8
4122 END IF
4123 END DO
4124
4125 IF (foundit(1)) THEN ! scale data
4126 DO i=1,asize(1)
4127 a(i)=afactor*a(i)
4128 END DO
4129 END IF
4130
4131 IF (foundit(2)) THEN ! add data offset
4132 DO i=1,asize(1)
4133 a(i)=a(i)+aoffset
4134 END DO
4135 END IF
4136 END IF
4137!
4138! Compute minimum and maximum values of read variable.
4139!
4140 IF (PRESENT(min_val)) THEN
4141 min_val=minval(a)
4142 END IF
4143 IF (PRESENT(max_val)) THEN
4144 max_val=maxval(a)
4145 END IF
4146!
4147! If file descriptor is not provided, close input NetCDF file.
4148!
4149 IF (.not.PRESENT(piofile)) THEN
4150 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
4151 END IF
4152!
4153 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_1D - error while reading ', &
4154 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
4155 & /,26x,'call from:',2x,a)
4156 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_1D - error while inquiring ', &
4157 & 'descriptor for variable:',2x,a,/,26x,'in input file:', &
4158 & 2x,a,/,26x,'call from:',2x,a)
4159!
4160 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, mod_scalars::spval_check, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_fvar_1dp()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_1dp ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(dp), dimension(:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(dp), intent(out), optional min_val,
real(dp), intent(out), optional max_val )

Definition at line 3153 of file mod_pio_netcdf.F.

3156!
3157!=======================================================================
3158! !
3159! This routine reads requested double-precision 1D-array variable !
3160! from specified NetCDF file. !
3161! !
3162! On Input: !
3163! !
3164! ng Nested grid number (integer) !
3165! model Calling model identifier (integer) !
3166! ncname NetCDF file name (string) !
3167! myVarName Variable name (string) !
3168! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
3169! pioFile%fh file handler !
3170! pioFile%iosystem IO system descriptor (struct) !
3171! start Starting index where the first of the data values !
3172! will be read along each dimension (integer, !
3173! OPTIONAL) !
3174! total Number of data values to be read along each !
3175! dimension (integer, OPTIONAL) !
3176! !
3177! broadcast Switch to broadcast read values from root to all !
3178! members of the communicator in distributed- !
3179! memory applications (logical, OPTIONAL). It is !
3180! ignored since PIO library broadcasts the values !
3181! to all member in the group by default. !
3182! !
3183! On Ouput: !
3184! !
3185! A Read 1D-array variable (double precision) !
3186! min_val Read data minimum value (double precision, OPTIONAL)!
3187! max_val Read data maximum value (double precision, OPTIONAL)!
3188! !
3189! Examples: !
3190! !
3191! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
3192! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(0:)) !
3193! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(:,1)) !
3194! !
3195!=======================================================================
3196!
3197! Imported variable declarations.
3198!
3199 logical, intent(in), optional :: broadcast
3200!
3201 integer, intent(in) :: ng, model
3202
3203 integer, intent(in), optional :: start(:)
3204 integer, intent(in), optional :: total(:)
3205!
3206 character (len=*), intent(in) :: ncname
3207 character (len=*), intent(in) :: myVarName
3208!
3209 real(dp), intent(out), optional :: min_val
3210 real(dp), intent(out), optional :: max_val
3211
3212 real(dp), intent(out) :: A(:)
3213!
3214 TYPE (File_desc_t), intent(in), optional :: pioFile
3215!
3216! Local variable declarations.
3217!
3218 logical, dimension(3) :: foundit
3219!
3220 integer :: i, status
3221
3222 integer, dimension(1) :: Asize
3223!
3224 real(dp) :: Afactor, Aoffset, Aspval
3225
3226 real(dp), parameter :: Aepsilon = 1.0e-8_r8
3227
3228 real(dp), dimension(3) :: AttValue
3229!
3230 character (len=12), dimension(3) :: AttName
3231
3232 character (len=*), parameter :: MyFile = &
3233 & __FILE__//", pio_netcdf_get_fvar_1dp"
3234!
3235 TYPE (File_desc_t) :: my_pioFile
3236 TYPE (Var_desc_t) :: my_pioVar
3237!
3238!-----------------------------------------------------------------------
3239! Read in a double-precision 1D-array variable.
3240!-----------------------------------------------------------------------
3241!
3242 IF (PRESENT(start).and.PRESENT(total)) THEN
3243 asize(1)=1
3244 DO i=1,SIZE(total) ! this logic is for the case
3245 asize(1)=asize(1)*total(i) ! of reading multidimensional
3246 END DO ! data into a compact 1D array
3247 ELSE
3248 asize(1)=ubound(a, dim=1)
3249 END IF
3250!
3251! If file descriptor is not provided, open NetCDF for reading.
3252!
3253 IF (.not.PRESENT(piofile)) THEN
3254 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
3255 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
3256 ELSE
3257 my_piofile=piofile
3258 END IF
3259!
3260! Read in variable.
3261!
3262 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
3263 IF (status.eq.pio_noerr) THEN
3264 IF (PRESENT(start).and.PRESENT(total)) THEN
3265 status=pio_get_var(my_piofile, my_piovar, start, total, a)
3266 ELSE
3267 status=pio_get_var(my_piofile, my_piovar, a)
3268 END IF
3269 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
3270 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
3271 & trim(sourcefile)
3272 exit_flag=2
3273 ioerror=status
3274 END IF
3275 ELSE
3276 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
3277 & trim(sourcefile)
3278 exit_flag=2
3279 ioerror=status
3280 END IF
3281!
3282! Check if the following attributes: "scale_factor", "add_offset", and
3283! "_FillValue" are present in the input NetCDF variable:
3284!
3285! If the "scale_value" attribute is present, the data is multiplied by
3286! this factor after reading.
3287! If the "add_offset" attribute is present, this value is added to the
3288! data after reading.
3289! If both "scale_factor" and "add_offset" attributes are present, the
3290! data are first scaled before the offset is added.
3291! If the "_FillValue" attribute is present, the data having this value
3292! is treated as missing and it is replaced with zero. This feature it
3293! is usually related with the land/sea masking.
3294!
3295 attname(1)='scale_factor'
3296 attname(2)='add_offset '
3297 attname(3)='_FillValue '
3298
3299 CALL pio_netcdf_get_fatt (ng, model, ncname, my_piovar, &
3300 & attname, attvalue, foundit, &
3301 & piofile = my_piofile)
3302
3303 IF (exit_flag.eq.noerror) THEN
3304 IF (.not.foundit(1)) THEN
3305 afactor=1.0_dp
3306 ELSE
3307 afactor=attvalue(1)
3308 END IF
3309
3310 IF (.not.foundit(2)) THEN
3311 aoffset=0.0_dp
3312 ELSE
3313 aoffset=attvalue(2)
3314 END IF
3315
3316 IF (.not.foundit(3)) THEN
3317 aspval=spval_check
3318 ELSE
3319 aspval=attvalue(3)
3320 END IF
3321
3322 DO i=1,asize(1) ! zero out missing values
3323 IF ((foundit(3).and.(abs(a(i)-aspval).lt.aepsilon)).or. &
3324 & (.not.foundit(3).and.(abs(a(i)).ge.abs(aspval)))) THEN
3325 a(i)=0.0_dp
3326 END IF
3327 END DO
3328
3329 IF (foundit(1)) THEN ! scale data
3330 DO i=1,asize(1)
3331 a(i)=afactor*a(i)
3332 END DO
3333 END IF
3334
3335 IF (foundit(2)) THEN ! add data offset
3336 DO i=1,asize(1)
3337 a(i)=a(i)+aoffset
3338 END DO
3339 END IF
3340 END IF
3341!
3342! Compute minimum and maximum values of read variable.
3343!
3344 IF (PRESENT(min_val)) THEN
3345 min_val=minval(a)
3346 END IF
3347 IF (PRESENT(max_val)) THEN
3348 max_val=maxval(a)
3349 END IF
3350!
3351! If file descriptor is not provided, close input NetCDF file.
3352!
3353 IF (.not.PRESENT(piofile)) THEN
3354 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
3355 END IF
3356!
3357 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_1DP - error while reading ', &
3358 & 'variable:',2x,a,/,27x,'in input file:',2x,a, &
3359 & /,27x,'call from:',2x,a)
3360 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_1DP - error while inquiring ', &
3361 & 'descriptor for variable:',2x,a,/,27x,'in input file:', &
3362 & 2x,a,/,27x,'call from:',2x,a)
3363!
3364 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, mod_scalars::spval_check, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_fvar_2d()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_2d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(r8), dimension(:,:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(r8), intent(out), optional min_val,
real(r8), intent(out), optional max_val )

Definition at line 4163 of file mod_pio_netcdf.F.

4166!
4167!=======================================================================
4168! !
4169! This routine reads requested floating-point 2D-array variable from !
4170! specified NetCDF file. !
4171! !
4172! On Input: !
4173! !
4174! ng Nested grid number (integer) !
4175! model Calling model identifier (integer) !
4176! ncname NetCDF file name (string) !
4177! myVarName Variable name (string) !
4178! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
4179! pioFile%fh file handler !
4180! pioFile%iosystem IO system descriptor (struct) !
4181! start Starting index where the first of the data values !
4182! will be read along each dimension (integer, !
4183! OPTIONAL) !
4184! total Number of data values to be read along each !
4185! dimension (integer, OPTIONAL) !
4186! broadcast Switch to broadcast read values from root to all !
4187! members of the communicator in distributed- !
4188! memory applications (logical, OPTIONAL). It is !
4189! ignored since PIO library broadcasts the values !
4190! to all member in the group by default. !
4191! !
4192! On Ouput: !
4193! !
4194! A Read 2D-array variable (real) !
4195! min_val Read data minimum value (real, OPTIONAL) !
4196! max_val Read data maximum value (real, OPTIONAL) !
4197! !
4198! Examples: !
4199! !
4200! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
4201! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(0:,:)) !
4202! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(0:,0:)) !
4203! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(:,:,1)) !
4204! !
4205!=======================================================================
4206!
4207! Imported variable declarations.
4208!
4209 logical, intent(in), optional :: broadcast
4210!
4211 integer, intent(in) :: ng, model
4212
4213 integer, intent(in), optional :: start(:)
4214 integer, intent(in), optional :: total(:)
4215!
4216 character (len=*), intent(in) :: ncname
4217 character (len=*), intent(in) :: myVarName
4218!
4219 real(r8), intent(out), optional :: min_val
4220 real(r8), intent(out), optional :: max_val
4221
4222 real(r8), intent(out) :: A(:,:)
4223!
4224 TYPE (File_desc_t), intent(in), optional :: pioFile
4225!
4226! Local variable declarations.
4227!
4228 logical, dimension(3) :: foundit
4229!
4230 integer :: i, j, status
4231
4232 integer, dimension(2) :: Asize
4233!
4234 real(r8) :: Afactor, Aoffset, Aspval
4235
4236 real(r8), parameter :: Aepsilon = 1.0e-8_r8
4237
4238 real(r8), dimension(3) :: AttValue
4239!
4240 character (len=12), dimension(3) :: AttName
4241
4242 character (len=*), parameter :: MyFile = &
4243 & __FILE__//", pio_netcdf_get_fvar_2d"
4244!
4245 TYPE (File_desc_t) :: my_pioFile
4246 TYPE (Var_desc_t) :: my_pioVar
4247!
4248!-----------------------------------------------------------------------
4249! Read in a floating-point 2D-array variable.
4250!-----------------------------------------------------------------------
4251!
4252 IF (PRESENT(start).and.PRESENT(total)) THEN
4253 asize(1)=total(1)
4254 asize(2)=total(2)
4255 ELSE
4256 asize(1)=ubound(a, dim=1)
4257 asize(2)=ubound(a, dim=2)
4258 END IF
4259!
4260! If file descriptor is not provided, open NetCDF for reading.
4261!
4262 IF (.not.PRESENT(piofile)) THEN
4263 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
4264 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
4265 ELSE
4266 my_piofile=piofile
4267 END IF
4268!
4269! Read in variable.
4270!
4271 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
4272 IF (status.eq.pio_noerr) THEN
4273 IF (PRESENT(start).and.PRESENT(total)) THEN
4274 status=pio_get_var(my_piofile, my_piovar, start, total, a)
4275 ELSE
4276 status=pio_get_var(my_piofile, my_piovar, a)
4277 END IF
4278 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
4279 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
4280 & trim(sourcefile)
4281 exit_flag=2
4282 ioerror=status
4283 END IF
4284 ELSE
4285 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
4286 & trim(sourcefile)
4287 exit_flag=2
4288 ioerror=status
4289 END IF
4290!
4291! Check if the following attributes: "scale_factor", "add_offset", and
4292! "_FillValue" are present in the input NetCDF variable:
4293!
4294! If the "scale_value" attribute is present, the data is multiplied by
4295! this factor after reading.
4296! If the "add_offset" attribute is present, this value is added to the
4297! data after reading.
4298! If both "scale_factor" and "add_offset" attributes are present, the
4299! data are first scaled before the offset is added.
4300! If the "_FillValue" attribute is present, the data having this value
4301! is treated as missing and it is replaced with zero. This feature it
4302! is usually related with the land/sea masking.
4303!
4304 attname(1)='scale_factor'
4305 attname(2)='add_offset '
4306 attname(3)='_FillValue '
4307
4308 CALL pio_netcdf_get_fatt (ng, model, ncname, my_piovar, &
4309 & attname, attvalue, foundit, &
4310 & piofile = my_piofile)
4311
4312 IF (exit_flag.eq.noerror) THEN
4313 IF (.not.foundit(1)) THEN
4314 afactor=1.0_r8
4315 ELSE
4316 afactor=attvalue(1)
4317 END IF
4318
4319 IF (.not.foundit(2)) THEN
4320 aoffset=0.0_r8
4321 ELSE
4322 aoffset=attvalue(2)
4323 END IF
4324
4325 IF (.not.foundit(3)) THEN
4326 aspval=spval_check
4327 ELSE
4328 aspval=attvalue(3)
4329 END IF
4330
4331 DO j=1,asize(2) ! zero out missing values
4332 DO i=1,asize(1)
4333 IF ((foundit(3).and.(abs(a(i,j)-aspval).lt.aepsilon)).or. &
4334 & (.not.foundit(3).and.(abs(a(i,j)).ge.abs(aspval)))) THEN
4335 a(i,j)=0.0_r8
4336 END IF
4337 END DO
4338 END DO
4339
4340 IF (foundit(1)) THEN ! scale data
4341 DO j=1,asize(2)
4342 DO i=1,asize(1)
4343 a(i,j)=afactor*a(i,j)
4344 END DO
4345 END DO
4346 END IF
4347
4348 IF (foundit(2)) THEN ! add data offset
4349 DO j=1,asize(2)
4350 DO i=1,asize(1)
4351 a(i,j)=a(i,j)+aoffset
4352 END DO
4353 END DO
4354 END IF
4355 END IF
4356!
4357! Compute minimum and maximum values of read variable.
4358!
4359 IF (PRESENT(min_val)) THEN
4360 min_val=minval(a)
4361 END IF
4362 IF (PRESENT(max_val)) THEN
4363 max_val=maxval(a)
4364 END IF
4365!
4366! If file descriptor is not provided, close input NetCDF file.
4367!
4368 IF (.not.PRESENT(piofile)) THEN
4369 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
4370 END IF
4371!
4372 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_2D - error while reading ', &
4373 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
4374 & /,26x,'call from:',2x,a)
4375 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_2D - error while inquiring ', &
4376 & 'descriptor for variable:',2x,a,/,26x,'in input file:', &
4377 & 2x,a,/,26x,'call from:',2x,a)
4378!
4379 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, mod_scalars::spval_check, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_fvar_2dp()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_2dp ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(dp), dimension(:,:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(dp), intent(out), optional min_val,
real(dp), intent(out), optional max_val )

Definition at line 3367 of file mod_pio_netcdf.F.

3370!
3371!=======================================================================
3372! !
3373! This routine reads requested double-precision 2D-array variable !
3374! from specified NetCDF file. !
3375! !
3376! On Input: !
3377! !
3378! ng Nested grid number (integer) !
3379! model Calling model identifier (integer) !
3380! ncname NetCDF file name (string) !
3381! myVarName Variable name (string) !
3382! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
3383! pioFile%fh file handler !
3384! pioFile%iosystem IO system descriptor (struct) !
3385! start Starting index where the first of the data values !
3386! will be read along each dimension (integer, !
3387! OPTIONAL) !
3388! total Number of data values to be read along each !
3389! dimension (integer, OPTIONAL) !
3390! broadcast Switch to broadcast read values from root to all !
3391! members of the communicator in distributed- !
3392! memory applications (logical, OPTIONAL). It is !
3393! ignored since PIO library broadcasts the values !
3394! to all member in the group by default. !
3395! !
3396! On Ouput: !
3397! !
3398! A Read 2D-array variable (real) !
3399! min_val Read data minimum value (real, OPTIONAL) !
3400! max_val Read data maximum value (real, OPTIONAL) !
3401! !
3402! Examples: !
3403! !
3404! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
3405! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(0:,:)) !
3406! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(0:,0:)) !
3407! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A(:,:,1)) !
3408! !
3409!=======================================================================
3410!
3411! Imported variable declarations.
3412!
3413 logical, intent(in), optional :: broadcast
3414!
3415 integer, intent(in) :: ng, model
3416
3417 integer, intent(in), optional :: start(:)
3418 integer, intent(in), optional :: total(:)
3419!
3420 character (len=*), intent(in) :: ncname
3421 character (len=*), intent(in) :: myVarName
3422!
3423 real(dp), intent(out), optional :: min_val
3424 real(dp), intent(out), optional :: max_val
3425
3426 real(dp), intent(out) :: A(:,:)
3427!
3428 TYPE (File_desc_t), intent(in), optional :: pioFile
3429!
3430! Local variable declarations.
3431!
3432 logical, dimension(3) :: foundit
3433!
3434 integer :: i, j, status
3435
3436 integer, dimension(2) :: Asize
3437!
3438 real(dp) :: Afactor, Aoffset, Aspval
3439
3440 real(dp), parameter :: Aepsilon = 1.0e-8_r8
3441
3442 real(dp), dimension(3) :: AttValue
3443!
3444 character (len=12), dimension(3) :: AttName
3445
3446 character (len=*), parameter :: MyFile = &
3447 & __FILE__//", pio_netcdf_get_fvar_2dp"
3448!
3449 TYPE (File_desc_t) :: my_pioFile
3450 TYPE (Var_desc_t) :: my_pioVar
3451!
3452!-----------------------------------------------------------------------
3453! Read in a floating-point 2D-array variable.
3454!-----------------------------------------------------------------------
3455!
3456 IF (PRESENT(start).and.PRESENT(total)) THEN
3457 asize(1)=total(1)
3458 asize(2)=total(2)
3459 ELSE
3460 asize(1)=ubound(a, dim=1)
3461 asize(2)=ubound(a, dim=2)
3462 END IF
3463!
3464! If file descriptor is not provided, open NetCDF for reading.
3465!
3466 IF (.not.PRESENT(piofile)) THEN
3467 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
3468 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
3469 ELSE
3470 my_piofile=piofile
3471 END IF
3472!
3473! Read in variable.
3474!
3475 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
3476 IF (status.eq.pio_noerr) THEN
3477 IF (PRESENT(start).and.PRESENT(total)) THEN
3478 status=pio_get_var(my_piofile, my_piovar, start, total, a)
3479 ELSE
3480 status=pio_get_var(my_piofile, my_piovar, a)
3481 END IF
3482 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
3483 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
3484 & trim(sourcefile)
3485 exit_flag=2
3486 ioerror=status
3487 END IF
3488 ELSE
3489 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
3490 & trim(sourcefile)
3491 exit_flag=2
3492 ioerror=status
3493 END IF
3494!
3495! Check if the following attributes: "scale_factor", "add_offset", and
3496! "_FillValue" are present in the input NetCDF variable:
3497!
3498! If the "scale_value" attribute is present, the data is multiplied by
3499! this factor after reading.
3500! If the "add_offset" attribute is present, this value is added to the
3501! data after reading.
3502! If both "scale_factor" and "add_offset" attributes are present, the
3503! data are first scaled before the offset is added.
3504! If the "_FillValue" attribute is present, the data having this value
3505! is treated as missing and it is replaced with zero. This feature it
3506! is usually related with the land/sea masking.
3507!
3508 attname(1)='scale_factor'
3509 attname(2)='add_offset '
3510 attname(3)='_FillValue '
3511
3512 CALL pio_netcdf_get_fatt (ng, model, ncname, my_piovar, &
3513 & attname, attvalue, foundit, &
3514 & piofile = my_piofile)
3515
3516 IF (exit_flag.eq.noerror) THEN
3517 IF (.not.foundit(1)) THEN
3518 afactor=1.0_r8
3519 ELSE
3520 afactor=attvalue(1)
3521 END IF
3522
3523 IF (.not.foundit(2)) THEN
3524 aoffset=0.0_r8
3525 ELSE
3526 aoffset=attvalue(2)
3527 END IF
3528
3529 IF (.not.foundit(3)) THEN
3530 aspval=spval_check
3531 ELSE
3532 aspval=attvalue(3)
3533 END IF
3534
3535 DO j=1,asize(2) ! zero out missing values
3536 DO i=1,asize(1)
3537 IF ((foundit(3).and.(abs(a(i,j)-aspval).lt.aepsilon)).or. &
3538 & (.not.foundit(3).and.(abs(a(i,j)).ge.abs(aspval)))) THEN
3539 a(i,j)=0.0_r8
3540 END IF
3541 END DO
3542 END DO
3543
3544 IF (foundit(1)) THEN ! scale data
3545 DO j=1,asize(2)
3546 DO i=1,asize(1)
3547 a(i,j)=afactor*a(i,j)
3548 END DO
3549 END DO
3550 END IF
3551
3552 IF (foundit(2)) THEN ! add data offset
3553 DO j=1,asize(2)
3554 DO i=1,asize(1)
3555 a(i,j)=a(i,j)+aoffset
3556 END DO
3557 END DO
3558 END IF
3559 END IF
3560!
3561! Compute minimum and maximum values of read variable.
3562!
3563 IF (PRESENT(min_val)) THEN
3564 min_val=minval(a)
3565 END IF
3566 IF (PRESENT(max_val)) THEN
3567 max_val=maxval(a)
3568 END IF
3569!
3570! If file descriptor is not provided, close input NetCDF file.
3571!
3572 IF (.not.PRESENT(piofile)) THEN
3573 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
3574 END IF
3575!
3576 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_2DP - error while reading ', &
3577 & 'variable:',2x,a,/,27x,'in input file:',2x,a, &
3578 & /,27x,'call from:',2x,a)
3579 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_2DP0 - error while inquiring ', &
3580 & 'descriptor for variable:',2x,a,/,27x,'in input file:', &
3581 & 2x,a,/,27x,'call from:',2x,a)
3582!
3583 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, mod_scalars::spval_check, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_fvar_3d()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_3d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(r8), dimension(:,:,:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(r8), intent(out), optional min_val,
real(r8), intent(out), optional max_val )

Definition at line 4382 of file mod_pio_netcdf.F.

4385!
4386!=======================================================================
4387! !
4388! This routine reads requested floating-point 3D-array variable from !
4389! specified NetCDF file. !
4390! !
4391! On Input: !
4392! !
4393! ng Nested grid number (integer) !
4394! model Calling model identifier (integer) !
4395! ncname NetCDF file name (string) !
4396! myVarName Variable name (string) !
4397! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
4398! pioFile%fh file handler !
4399! pioFile%iosystem IO system descriptor (struct) !
4400! start Starting index where the first of the data values !
4401! will be read along each dimension (integer, !
4402! OPTIONAL) !
4403! total Number of data values to be read along each !
4404! dimension (integer, OPTIONAL) !
4405! broadcast Switch to broadcast read values from root to all !
4406! members of the communicator in distributed- !
4407! memory applications (logical, OPTIONAL). It is !
4408! ignored since PIO library broadcasts the values !
4409! to all member in the group by default. !
4410! !
4411! On Ouput: !
4412! !
4413! A Read 3D-array variable (real) !
4414! min_val Read data minimum value (real, OPTIONAL) !
4415! max_val Read data maximum value (real, OPTIONAL) !
4416! !
4417! Examples: !
4418! !
4419! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
4420! !
4421!=======================================================================
4422!
4423! Imported variable declarations.
4424!
4425 logical, intent(in), optional :: broadcast
4426!
4427 integer, intent(in) :: ng, model
4428
4429 integer, intent(in), optional :: start(:)
4430 integer, intent(in), optional :: total(:)
4431!
4432 character (len=*), intent(in) :: ncname
4433 character (len=*), intent(in) :: myVarName
4434!
4435 real(r8), intent(out), optional :: min_val
4436 real(r8), intent(out), optional :: max_val
4437
4438 real(r8), intent(out) :: A(:,:,:)
4439!
4440 TYPE (File_desc_t), intent(in), optional :: pioFile
4441!
4442! Local variable declarations.
4443!
4444 logical, dimension(3) :: foundit
4445!
4446 integer :: i, j, k, status
4447
4448 integer, dimension(3) :: Asize
4449!
4450 real(r8) :: Afactor, Aoffset, Aspval
4451
4452 real(r8), parameter :: Aepsilon = 1.0e-8_r8
4453
4454 real(r8), dimension(3) :: AttValue
4455!
4456 character (len=12), dimension(3) :: AttName
4457
4458 character (len=*), parameter :: MyFile = &
4459 & __FILE__//", pio_netcdf_get_fvar_3d"
4460!
4461 TYPE (File_desc_t) :: my_pioFile
4462 TYPE (Var_desc_t) :: my_pioVar
4463!
4464!-----------------------------------------------------------------------
4465! Read in a floating-point 2D-array variable.
4466!-----------------------------------------------------------------------
4467!
4468 IF (PRESENT(start).and.PRESENT(total)) THEN
4469 asize(1)=total(1)
4470 asize(2)=total(2)
4471 asize(3)=total(3)
4472 ELSE
4473 asize(1)=ubound(a, dim=1)
4474 asize(2)=ubound(a, dim=2)
4475 asize(3)=ubound(a, dim=3)
4476 END IF
4477!
4478! If file descriptor is not provided, open NetCDF for reading.
4479!
4480 IF (.not.PRESENT(piofile)) THEN
4481 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
4482 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
4483 ELSE
4484 my_piofile=piofile
4485 END IF
4486!
4487! Read in variable.
4488!
4489 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
4490 IF (status.eq.pio_noerr) THEN
4491 IF (PRESENT(start).and.PRESENT(total)) THEN
4492 status=pio_get_var(my_piofile, my_piovar, start, total, a)
4493 ELSE
4494 status=pio_get_var(my_piofile, my_piovar, a)
4495 END IF
4496 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
4497 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
4498 & trim(sourcefile)
4499 exit_flag=2
4500 ioerror=status
4501 END IF
4502 ELSE
4503 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
4504 & trim(sourcefile)
4505 exit_flag=2
4506 ioerror=status
4507 END IF
4508!
4509! Check if the following attributes: "scale_factor", "add_offset", and
4510! "_FillValue" are present in the input NetCDF variable:
4511!
4512! If the "scale_value" attribute is present, the data is multiplied by
4513! this factor after reading.
4514! If the "add_offset" attribute is present, this value is added to the
4515! data after reading.
4516! If both "scale_factor" and "add_offset" attributes are present, the
4517! data are first scaled before the offset is added.
4518! If the "_FillValue" attribute is present, the data having this value
4519! is treated as missing and it is replaced with zero. This feature it
4520! is usually related with the land/sea masking.
4521!
4522 attname(1)='scale_factor'
4523 attname(2)='add_offset '
4524 attname(3)='_FillValue '
4525
4526 CALL pio_netcdf_get_fatt (ng, model, ncname, my_piovar, &
4527 & attname, attvalue, foundit, &
4528 & piofile = my_piofile)
4529
4530 IF (exit_flag.eq.noerror) THEN
4531 IF (.not.foundit(1)) THEN
4532 afactor=1.0_r8
4533 ELSE
4534 afactor=attvalue(1)
4535 END IF
4536
4537 IF (.not.foundit(2)) THEN
4538 aoffset=0.0_r8
4539 ELSE
4540 aoffset=attvalue(2)
4541 END IF
4542
4543 IF (.not.foundit(3)) THEN
4544 aspval=spval_check
4545 ELSE
4546 aspval=attvalue(3)
4547 END IF
4548
4549 DO k=1,asize(3) ! zero out missing values
4550 DO j=1,asize(2)
4551 DO i=1,asize(1)
4552 IF ((foundit(3).and. &
4553 & (abs(a(i,j,k)-aspval).lt.aepsilon)).or. &
4554 & (.not.foundit(3).and. &
4555 & (abs(a(i,j,k)).ge.abs(aspval)))) THEN
4556 a(i,j,k)=0.0_r8
4557 END IF
4558 END DO
4559 END DO
4560 END DO
4561
4562 IF (foundit(1)) THEN ! scale data
4563 DO k=1,asize(3)
4564 DO j=1,asize(2)
4565 DO i=1,asize(1)
4566 a(i,j,k)=afactor*a(i,j,k)
4567 END DO
4568 END DO
4569 END DO
4570 END IF
4571
4572 IF (foundit(2)) THEN ! add data offset
4573 DO k=1,asize(3)
4574 DO j=1,asize(2)
4575 DO i=1,asize(1)
4576 a(i,j,k)=a(i,j,k)+aoffset
4577 END DO
4578 END DO
4579 END DO
4580 END IF
4581 END IF
4582!
4583! Compute minimum and maximum values of read variable.
4584!
4585 IF (PRESENT(min_val)) THEN
4586 min_val=minval(a)
4587 END IF
4588 IF (PRESENT(max_val)) THEN
4589 max_val=maxval(a)
4590 END IF
4591!
4592! If file descriptor is not provided, close input NetCDF file.
4593!
4594 IF (.not.PRESENT(piofile)) THEN
4595 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
4596 END IF
4597!
4598 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_3D - error while reading ', &
4599 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
4600 & /,26x,'call from:',2x,a)
4601 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_3D - error while inquiring ', &
4602 & 'descriptor for variable:',2x,a,/,26x,'in input file:', &
4603 & 2x,a,/,26x,'call from:',2x,a)
4604!
4605 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, mod_scalars::spval_check, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_fvar_3dp()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_3dp ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(dp), dimension(:,:,:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(dp), intent(out), optional min_val,
real(dp), intent(out), optional max_val )

Definition at line 3586 of file mod_pio_netcdf.F.

3589!
3590!=======================================================================
3591! !
3592! This routine reads requested double-precision 3D-array variable !
3593! from specified NetCDF file. !
3594! !
3595! On Input: !
3596! !
3597! ng Nested grid number (integer) !
3598! model Calling model identifier (integer) !
3599! ncname NetCDF file name (string) !
3600! myVarName Variable name (string) !
3601! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
3602! pioFile%fh file handler !
3603! pioFile%iosystem IO system descriptor (struct) !
3604! start Starting index where the first of the data values !
3605! will be read along each dimension (integer, !
3606! OPTIONAL) !
3607! total Number of data values to be read along each !
3608! dimension (integer, OPTIONAL) !
3609! broadcast Switch to broadcast read values from root to all !
3610! members of the communicator in distributed- !
3611! memory applications (logical, OPTIONAL). It is !
3612! ignored since PIO library broadcasts the values !
3613! to all member in the group by default. !
3614! !
3615! On Ouput: !
3616! !
3617! A Read 3D-array variable (real) !
3618! min_val Read data minimum value (real, OPTIONAL) !
3619! max_val Read data maximum value (real, OPTIONAL) !
3620! !
3621! Examples: !
3622! !
3623! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
3624! !
3625!=======================================================================
3626!
3627! Imported variable declarations.
3628!
3629 logical, intent(in), optional :: broadcast
3630!
3631 integer, intent(in) :: ng, model
3632
3633 integer, intent(in), optional :: start(:)
3634 integer, intent(in), optional :: total(:)
3635!
3636 character (len=*), intent(in) :: ncname
3637 character (len=*), intent(in) :: myVarName
3638!
3639 real(dp), intent(out), optional :: min_val
3640 real(dp), intent(out), optional :: max_val
3641
3642 real(dp), intent(out) :: A(:,:,:)
3643!
3644 TYPE (File_desc_t), intent(in), optional :: pioFile
3645!
3646! Local variable declarations.
3647!
3648 logical, dimension(3) :: foundit
3649!
3650 integer :: i, j, k, status
3651
3652 integer, dimension(3) :: Asize
3653!
3654 real(dp) :: Afactor, Aoffset, Aspval
3655
3656 real(dp), parameter :: Aepsilon = 1.0e-8_r8
3657
3658 real(dp), dimension(3) :: AttValue
3659!
3660 character (len=12), dimension(3) :: AttName
3661
3662 character (len=*), parameter :: MyFile = &
3663 & __FILE__//", pio_netcdf_get_fvar_3dp"
3664!
3665 TYPE (File_desc_t) :: my_pioFile
3666 TYPE (Var_desc_t) :: my_pioVar
3667!
3668!-----------------------------------------------------------------------
3669! Read in a floating-point 2D-array variable.
3670!-----------------------------------------------------------------------
3671!
3672 IF (PRESENT(start).and.PRESENT(total)) THEN
3673 asize(1)=total(1)
3674 asize(2)=total(2)
3675 asize(3)=total(3)
3676 ELSE
3677 asize(1)=ubound(a, dim=1)
3678 asize(2)=ubound(a, dim=2)
3679 asize(3)=ubound(a, dim=3)
3680 END IF
3681!
3682! If file descriptor is not provided, open NetCDF for reading.
3683!
3684 IF (.not.PRESENT(piofile)) THEN
3685 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
3686 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
3687 ELSE
3688 my_piofile=piofile
3689 END IF
3690!
3691! Read in variable.
3692!
3693 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
3694 IF (status.eq.pio_noerr) THEN
3695 IF (PRESENT(start).and.PRESENT(total)) THEN
3696 status=pio_get_var(my_piofile, my_piovar, start, total, a)
3697 ELSE
3698 status=pio_get_var(my_piofile, my_piovar, a)
3699 END IF
3700 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
3701 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
3702 & trim(sourcefile)
3703 exit_flag=2
3704 ioerror=status
3705 END IF
3706 ELSE
3707 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
3708 & trim(sourcefile)
3709 exit_flag=2
3710 ioerror=status
3711 END IF
3712!
3713! Check if the following attributes: "scale_factor", "add_offset", and
3714! "_FillValue" are present in the input NetCDF variable:
3715!
3716! If the "scale_value" attribute is present, the data is multiplied by
3717! this factor after reading.
3718! If the "add_offset" attribute is present, this value is added to the
3719! data after reading.
3720! If both "scale_factor" and "add_offset" attributes are present, the
3721! data are first scaled before the offset is added.
3722! If the "_FillValue" attribute is present, the data having this value
3723! is treated as missing and it is replaced with zero. This feature it
3724! is usually related with the land/sea masking.
3725!
3726 attname(1)='scale_factor'
3727 attname(2)='add_offset '
3728 attname(3)='_FillValue '
3729
3730 CALL pio_netcdf_get_fatt (ng, model, ncname, my_piovar, &
3731 & attname, attvalue, foundit, &
3732 & piofile = my_piofile)
3733
3734 IF (exit_flag.eq.noerror) THEN
3735 IF (.not.foundit(1)) THEN
3736 afactor=1.0_r8
3737 ELSE
3738 afactor=attvalue(1)
3739 END IF
3740
3741 IF (.not.foundit(2)) THEN
3742 aoffset=0.0_r8
3743 ELSE
3744 aoffset=attvalue(2)
3745 END IF
3746
3747 IF (.not.foundit(3)) THEN
3748 aspval=spval_check
3749 ELSE
3750 aspval=attvalue(3)
3751 END IF
3752
3753 DO k=1,asize(3) ! zero out missing values
3754 DO j=1,asize(2)
3755 DO i=1,asize(1)
3756 IF ((foundit(3).and. &
3757 & (abs(a(i,j,k)-aspval).lt.aepsilon)).or. &
3758 & (.not.foundit(3).and. &
3759 & (abs(a(i,j,k)).ge.abs(aspval)))) THEN
3760 a(i,j,k)=0.0_r8
3761 END IF
3762 END DO
3763 END DO
3764 END DO
3765
3766 IF (foundit(1)) THEN ! scale data
3767 DO k=1,asize(3)
3768 DO j=1,asize(2)
3769 DO i=1,asize(1)
3770 a(i,j,k)=afactor*a(i,j,k)
3771 END DO
3772 END DO
3773 END DO
3774 END IF
3775
3776 IF (foundit(2)) THEN ! add data offset
3777 DO k=1,asize(3)
3778 DO j=1,asize(2)
3779 DO i=1,asize(1)
3780 a(i,j,k)=a(i,j,k)+aoffset
3781 END DO
3782 END DO
3783 END DO
3784 END IF
3785 END IF
3786!
3787! Compute minimum and maximum values of read variable.
3788!
3789 IF (PRESENT(min_val)) THEN
3790 min_val=minval(a)
3791 END IF
3792 IF (PRESENT(max_val)) THEN
3793 max_val=maxval(a)
3794 END IF
3795!
3796! If file descriptor is not provided, close input NetCDF file.
3797!
3798 IF (.not.PRESENT(piofile)) THEN
3799 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
3800 END IF
3801!
3802 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_3DP - error while reading ', &
3803 & 'variable:',2x,a,/,27x,'in input file:',2x,a, &
3804 & /,27x,'call from:',2x,a)
3805 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_3DP - error while inquiring ', &
3806 & 'descriptor for variable:',2x,a,/,27x,'in input file:', &
3807 & 2x,a,/,27x,'call from:',2x,a)
3808!
3809 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, mod_scalars::spval_check, and mod_iounits::stdout.

Here is the call graph for this function:

◆ pio_netcdf_get_fvar_4d()

subroutine mod_pio_netcdf::pio_netcdf_get_fvar::pio_netcdf_get_fvar_4d ( integer, intent(in) ng,
integer, intent(in) model,
character (len=*), intent(in) ncname,
character (len=*), intent(in) myvarname,
real(r8), dimension(:,:,:,:), intent(out) a,
type (file_desc_t), intent(in), optional piofile,
integer, dimension(:), intent(in), optional start,
integer, dimension(:), intent(in), optional total,
logical, intent(in), optional broadcast,
real(r8), intent(out), optional min_val,
real(r8), intent(out), optional max_val )

Definition at line 4608 of file mod_pio_netcdf.F.

4611!
4612!=======================================================================
4613! !
4614! This routine reads requested floating-point 4D-array variable from !
4615! specified NetCDF file. !
4616! !
4617! On Input: !
4618! !
4619! ng Nested grid number (integer) !
4620! model Calling model identifier (integer) !
4621! ncname NetCDF file name (string) !
4622! myVarName Variable name (string) !
4623! pioFile PIO file descriptor, TYPE(File_desc_t), OPTIONAL !
4624! pioFile%fh file handler !
4625! pioFile%iosystem IO system descriptor (struct) !
4626! start Starting index where the first of the data values !
4627! will be read along each dimension (integer, !
4628! OPTIONAL) !
4629! total Number of data values to be read along each !
4630! dimension (integer, OPTIONAL) !
4631! broadcast Switch to broadcast read values from root to all !
4632! members of the communicator in distributed- !
4633! memory applications (logical, OPTIONAL, !
4634! default=TRUE) !
4635! !
4636! On Ouput: !
4637! !
4638! A Read 4D-array variable (real) !
4639! min_val Read data minimum value (real, OPTIONAL) !
4640! max_val Read data maximum value (real, OPTIONAL) !
4641! !
4642! Examples: !
4643! !
4644! CALL pio_netcdf_get_fvar (ng, iNLM, 'f.nc', 'VarName', A) !
4645! !
4646!=======================================================================
4647!
4648! Imported variable declarations.
4649!
4650 logical, intent(in), optional :: broadcast
4651!
4652 integer, intent(in) :: ng, model
4653
4654 integer, intent(in), optional :: start(:)
4655 integer, intent(in), optional :: total(:)
4656!
4657 character (len=*), intent(in) :: ncname
4658 character (len=*), intent(in) :: myVarName
4659!
4660 real(r8), intent(out), optional :: min_val
4661 real(r8), intent(out), optional :: max_val
4662
4663 real(r8), intent(out) :: A(:,:,:,:)
4664!
4665 TYPE (File_desc_t), intent(in), optional :: pioFile
4666!
4667! Local variable declarations.
4668!
4669 logical, dimension(3) :: foundit
4670!
4671 integer :: i, j, k, l, status
4672
4673 integer, dimension(4) :: Asize
4674!
4675 real(r8) :: Afactor, Aoffset, Aspval
4676
4677 real(r8), parameter :: Aepsilon = 1.0e-8_r8
4678
4679 real(r8), dimension(3) :: AttValue
4680!
4681 character (len=12), dimension(3) :: AttName
4682
4683 character (len=*), parameter :: MyFile = &
4684 & __FILE__//", pio_netcdf_get_fvar_4d"
4685!
4686 TYPE (File_desc_t) :: my_pioFile
4687 TYPE (Var_desc_t) :: my_pioVar
4688!
4689!-----------------------------------------------------------------------
4690! Read in a floating-point 2D-array variable.
4691!-----------------------------------------------------------------------
4692!
4693 IF (PRESENT(start).and.PRESENT(total)) THEN
4694 asize(1)=total(1)
4695 asize(2)=total(2)
4696 asize(3)=total(3)
4697 asize(4)=total(4)
4698 ELSE
4699 asize(1)=ubound(a, dim=1)
4700 asize(2)=ubound(a, dim=2)
4701 asize(3)=ubound(a, dim=3)
4702 asize(4)=ubound(a, dim=4)
4703 END IF
4704!
4705! If file descriptor is not provided, open NetCDF for reading.
4706!
4707 IF (.not.PRESENT(piofile)) THEN
4708 CALL pio_netcdf_open (ng, model, trim(ncname), 0, my_piofile)
4709 IF (founderror(exit_flag, noerror, __line__, myfile)) RETURN
4710 ELSE
4711 my_piofile=piofile
4712 END IF
4713!
4714! Read in variable.
4715!
4716 status=pio_inq_varid(my_piofile, trim(myvarname), my_piovar)
4717 IF (status.eq.pio_noerr) THEN
4718 IF (PRESENT(start).and.PRESENT(total)) THEN
4719 status=pio_get_var(my_piofile, my_piovar, start, total, a)
4720 ELSE
4721 status=pio_get_var(my_piofile, my_piovar, a)
4722 END IF
4723 IF (founderror(status, pio_noerr, __line__, myfile)) THEN
4724 IF (master) WRITE (stdout,10) trim(myvarname), trim(ncname), &
4725 & trim(sourcefile)
4726 exit_flag=2
4727 ioerror=status
4728 END IF
4729 ELSE
4730 IF (master) WRITE (stdout,20) trim(myvarname), trim(ncname), &
4731 & trim(sourcefile)
4732 exit_flag=2
4733 ioerror=status
4734 END IF
4735!
4736! Check if the following attributes: "scale_factor", "add_offset", and
4737! "_FillValue" are present in the input NetCDF variable:
4738!
4739! If the "scale_value" attribute is present, the data is multiplied by
4740! this factor after reading.
4741! If the "add_offset" attribute is present, this value is added to the
4742! data after reading.
4743! If both "scale_factor" and "add_offset" attributes are present, the
4744! data are first scaled before the offset is added.
4745! If the "_FillValue" attribute is present, the data having this value
4746! is treated as missing and it is replaced with zero. This feature it
4747! is usually related with the land/sea masking.
4748!
4749 attname(1)='scale_factor'
4750 attname(2)='add_offset '
4751 attname(3)='_FillValue '
4752
4753 CALL pio_netcdf_get_fatt (ng, model, ncname, my_piovar, &
4754 & attname, attvalue, foundit, &
4755 & piofile = my_piofile)
4756
4757 IF (exit_flag.eq.noerror) THEN
4758 IF (.not.foundit(1)) THEN
4759 afactor=1.0_r8
4760 ELSE
4761 afactor=attvalue(1)
4762 END IF
4763
4764 IF (.not.foundit(2)) THEN
4765 aoffset=0.0_r8
4766 ELSE
4767 aoffset=attvalue(2)
4768 END IF
4769
4770 IF (.not.foundit(3)) THEN
4771 aspval=spval_check
4772 ELSE
4773 aspval=attvalue(3)
4774 END IF
4775
4776 DO l=1,asize(4) ! zero out missing values
4777 DO k=1,asize(3)
4778 DO j=1,asize(2)
4779 DO i=1,asize(1)
4780 IF ((foundit(3).and. &
4781 & (abs(a(i,j,k,l)-aspval).lt.aepsilon)).or. &
4782 & (.not.foundit(3).and. &
4783 & (abs(a(i,j,k,l)).ge.abs(aspval)))) THEN
4784 a(i,j,k,l)=0.0_r8
4785 END IF
4786 END DO
4787 END DO
4788 END DO
4789 END DO
4790
4791 IF (foundit(1)) THEN ! scale data
4792 DO l=1,asize(4)
4793 DO k=1,asize(3)
4794 DO j=1,asize(2)
4795 DO i=1,asize(1)
4796 a(i,j,k,l)=afactor*a(i,j,k,l)
4797 END DO
4798 END DO
4799 END DO
4800 END DO
4801 END IF
4802
4803 IF (foundit(2)) THEN ! add data offset
4804 DO l=1,asize(4)
4805 DO k=1,asize(3)
4806 DO j=1,asize(2)
4807 DO i=1,asize(1)
4808 a(i,j,k,l)=a(i,j,k,l)+aoffset
4809 END DO
4810 END DO
4811 END DO
4812 END DO
4813 END IF
4814 END IF
4815!
4816! Compute minimum and maximum values of read variable.
4817!
4818 IF (PRESENT(min_val)) THEN
4819 min_val=minval(a)
4820 END IF
4821 IF (PRESENT(max_val)) THEN
4822 max_val=maxval(a)
4823 END IF
4824!
4825! If file descriptor is not provided, close input NetCDF file.
4826!
4827 IF (.not.PRESENT(piofile)) THEN
4828 CALL pio_netcdf_close (ng, model, my_piofile, ncname, .false.)
4829 END IF
4830!
4831 10 FORMAT (/,' PIO_NETCDF_GET_FVAR_4D - error while reading ', &
4832 & 'variable:',2x,a,/,26x,'in input file:',2x,a, &
4833 & /,26x,'call from:',2x,a)
4834 20 FORMAT (/,' PIO_NETCDF_GET_FVAR_4D - error while inquiring ', &
4835 & 'descriptor for variable:',2x,a,/,26x,'in input file:', &
4836 & 2x,a,/,26x,'call from:',2x,a)
4837!
4838 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, mod_scalars::spval_check, and mod_iounits::stdout.

Here is the call graph for this function:

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