UPP (upp-srw-2.2.0)
Loading...
Searching...
No Matches
getVariable.f
1!!!@PROCESS NOEXTCHK
2subroutine getvariable(fileName,DateStr,dh,VarName,VarBuff,IM,JSTA_2L,JEND_2U,LM,IM1,JS,JE,LM1)
3
4
5! SUBPROGRAM DOCUMENTATION BLOCK
6! . . .
7! SUBPROGRAM: getVariable Read data from WRF output
8! PRGRMMR: MIKE BALDWIN ORG: NSSL/SPC DATE: 2002-04-08
9!
10! ABSTRACT: THIS ROUTINE READS DATA FROM A WRF OUTPUT FILE
11! USING WRF I/O API.
12! .
13!
14! PROGRAM HISTORY LOG:
15!
16! USAGE: CALL getVariable(fileName,DateStr,dh,VarName,VarBuff,IM,JSTA_2L,JEND_2U,LM,IM1,JS,JE,LM1)
17!
18! INPUT ARGUMENT LIST:
19! fileName : Character(len=256) : name of WRF output file
20! DateStr : Character(len=19) : date/time of requested variable
21! dh : integer : data handle
22! VarName : Character(len=31) : variable name
23! IM : integer : X dimension of data array
24! JSTA_2L : integer : start Y dimension of data array
25! JEND_2U : integer : end Y dimension of data array
26! LM : integer : Z dimension of data array
27! IM1 : integer : amount of data pulled in X dimension
28! JS : integer : start Y dimension of amount of data array pulled
29! JE : integer : end Y dimension of amount of data array pulled
30! LM1 : integer : amount of data pulled in Z dimension
31!
32! data is flipped in the Z dimension from what is originally given
33! the code requires the Z dimension to increase with pressure
34!
35! OUTPUT ARGUMENT LIST:
36! VarBuff : real(IM,JSTA_2L:JEND_2U,LM) : requested data array
37!
38! OUTPUT FILES:
39! NONE
40!
41! SUBPROGRAMS CALLED:
42! UTILITIES:
43! NONE
44! LIBRARY:
45! WRF I/O API
46! NETCDF
47
48 ! This subroutine reads the values of the variable named VarName into the buffer
49 ! VarBuff. VarBuff is filled with data only for I=1,IM1 and for J=JS,JE
50 ! and for L=1,Lm1, presumably this will be
51 ! the portion of VarBuff that is needed for this task.
52 ! use mpi
53 use wrf_io_flags_mod, only: wrf_real, wrf_real8
54!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
55 implicit none
56
57 include "mpif.h"
58
59!
60 character(len=256) ,intent(in) :: fileName
61 character(len=19) ,intent(in) :: DateStr
62 integer ,intent(in) :: dh
63 character(*) ,intent(in) :: VarName
64 real,intent(out) :: VarBuff(IM,JSTA_2L:JEND_2U,LM)
65 integer,intent(in) :: IM,LM,JSTA_2L,JEND_2U
66 integer,intent(in) :: IM1,LM1,JS,JE
67 integer :: ndim
68 integer :: WrfType,i,j,l,ll
69 integer, dimension(4) :: start_index, end_index
70 character (len= 4) :: staggering
71 character (len= 3) :: ordering
72 character (len=80), dimension(3) :: dimnames
73 real, allocatable, dimension(:,:,:,:) :: data
74 integer :: ierr,size,mype,idsize,ier
75 character(len=132) :: Stagger
76 real SPVAL
77
78! call set_wrf_debug_level ( 1 )
79 call mpi_comm_rank(mpi_comm_world,mype,ier)
80 start_index = 1
81 end_index = 1
82! print*,'SPVAL in getVariable = ',SPVAL
83 call ext_ncd_get_var_info(dh,trim(varname),ndim,ordering,stagger,start_index,end_index,wrftype,ierr)
84 IF ( ierr /= 0 ) THEN
85 write(*,*)'Error: ',ierr,trim(varname),' not found in ',filename
86 varbuff=0.
87 return
88 ENDIF
89 allocate(data (end_index(1), end_index(2), end_index(3), 1))
90 if( wrftype /= wrf_real .AND. wrftype /= wrf_real8 ) then !Ignore if not a real variable
91 write(*,*) 'Error: Not a real variable',wrftype
92 return
93 endif
94! write(*,'(A9,1x,I1,3(1x,I3),1x,A,1x,A)')&
95! trim(VarName), ndim, end_index(1), end_index(2), end_index(3), &
96! trim(ordering), trim(DateStr)
97! allocate(data (end_index(1), end_index(2), end_index(3), 1))
98! call ext_ncd_read_field(dh,DateStr,TRIM(VarName),data,WrfType,0,0,0,ordering,&
99! CHANGE WrfType to WRF_REAL BECAUSE THIS TELLS WRF IO API TO CONVERT TO REAL
100 print *,' GWVX XT_NCD GET FIELD',size(data), size(varbuff),mype
101 idsize=size(data)
102 if(mype == 0) then
103 call ext_ncd_read_field(dh,datestr,trim(varname),data,wrftype,0,0,0,ordering,&
104 staggering, dimnames , &
105 start_index,end_index, & !dom
106 start_index,end_index, & !mem
107 start_index,end_index, & !pat
108 ierr)
109 endif
110 call mpi_bcast(data,idsize,mpi_real,0,mpi_comm_world,ierr)
111 IF ( ierr /= 0 ) THEN
112 write(*,*)'Error reading ',varname,' from ',filename
113 write(*,*)' ndim = ', ndim
114 write(*,*)' end_index(1) ',end_index(1)
115 write(*,*)' end_index(2) ',end_index(2)
116 write(*,*)' end_index(3) ',end_index(3)
117 varbuff = 0.0
118 return
119 ENDIF
120 if (im1>end_index(1)) write(*,*) 'Err:',varname,' IM1=',im1,&
121 ' but data dim=',end_index(1)
122 if (je>end_index(2)) write(*,*) 'Err:',varname,' JE=',je,&
123 ' but data dim=',end_index(2)
124 if (lm1>end_index(3)) write(*,*) 'Err:',varname,' LM1=',lm1,&
125 ' but data dim=',end_index(3)
126 if (ndim>3) then
127 write(*,*) 'Error: ndim = ',ndim
128 endif
129 do l=1,lm1
130 ll=lm1-l+1 ! flip the z axis not sure about soil
131 do i=1,im1
132 do j=js,je
133 varbuff(i,j,l)=data(i,j,ll,1)
134 enddo
135 enddo
136! write(*,*) Varname,' L ',l,': = ',data(1,1,ll,1)
137 enddo
138 deallocate(data)
139 return
140
141end subroutine getvariable