Update version info for release v4.6.1 (#2122)
[WRF.git] / var / obsproc / src / module_inside.F90
blobaec33c23754498e95585fa7c9466e7da3fe575d2
2 MODULE module_inside
4 !------------------------------------------------------------------------------!
5 ! Check if an obs defined by it latitude, longitude and time is in the
6 ! MM5 horizontal domain (as defined in the namelist) and within the
7 ! time window (as defined in the namelist)
9 ! D. GILL,         April 1998
10 ! F. VANDENBERGHE, March 2001
11 !------------------------------------------------------------------------------!
13 USE module_type
14 USE module_func
15 USE module_mm5
16 USE map_utils
17 USE module_namelist
19 CONTAINS
20 ! ----------------------------------------------------------------------------
21 ! SUBROUTINE inside_domain ( lat , lon , ins , jew, outside_domain, &
22 !                            xjc,  yic,  xjd,  yid)
23 ! SUBROUTINE inside_window (time_obs, time_window_min, time_window_max, &
24 !                           outside_window, iunit)
25 ! ----------------------------------------------------------------------------
27 !\f
28 ! ----------------------------------------------------------------------------
30 SUBROUTINE inside_domain ( lat , lon , ins , jew, outside_domain, &
31                            xjc_out,  yic_out,  xjd_out,  yid_out)
33 !  This routine determines if an observation with the input latitude and
34 !  longitude is within the current domain.
36    USE module_map
38    IMPLICIT NONE
40    REAL ,    INTENT(IN)  :: lat , lon
41    INTEGER , INTENT(IN)  :: ins , jew
42    LOGICAL , INTENT(OUT) :: outside_domain
43    REAL ,    OPTIONAL    :: xjc_out , yic_out
44    REAL ,    OPTIONAL    :: xjd_out , yid_out
46    !  Local data
48    REAL                  :: xjd , yid
51    IF ( ABS(lat) .GT. 90. ) THEN
53       outside_domain = .TRUE.
55    ELSE
56      if (fg_format == 'MM5') then
57        CALL llxy (lat , lon , xjd , yid )
58      else if (fg_format == 'WRF') then
59        call latlon_to_ij(map_info, lat, lon, xjd, yid)
60        xjd = xjd + .5
61        yid = yid + .5
62      endif
63    
64       IF ((yid .GE. 1.) .AND. (yid .LE. ins  )  .AND. & 
65           (xjd .GE. 1.) .AND. (xjd .LE. jew  )) THEN
67            outside_domain = .FALSE.
69       ELSE
70         
71            outside_domain = .TRUE.
73 !        if(user_defined_area) then
74 !           if(xjd < x_left   .or. xjd > x_right .or. &
75 !              yid < y_bottom .or. yid > y_top) then
76 !              outside_domain = .FALSE.
77 !           end if
78 !        end if
80       END IF
82    END IF
84    IF (PRESENT (xjc_out)) THEN
85        xjc_out = xjd - 0.5
86        IF (PRESENT (yic_out)) THEN
87            yic_out = yid - 0.5
88            IF (PRESENT (xjd_out)) THEN
89                xjd_out = xjd
90                IF (PRESENT (yid_out)) THEN
91                    yid_out = yid
92                ENDIF
93            ENDIF
94        ENDIF
95    ENDIF
97         
98 END SUBROUTINE inside_domain
99        
101 ! ----------------------------------------------------------------------------
103 SUBROUTINE inside_window (time_obs, time_window_min, time_window_max, &
104                           outside_window, iunit)
106 !  This routine determines if an observation with the input time
107 !  is within the analysis time window ]time_window_min, time_window_max]
109    USE module_date
111    IMPLICIT NONE
113    CHARACTER (LEN = 14) :: time_obs
114    CHARACTER (LEN = 19) :: time_window_min
115    CHARACTER (LEN = 19) :: time_window_max
116    LOGICAL, INTENT(OUT) :: outside_window
117    INTEGER, INTENT(IN), OPTIONAL :: iunit
118    CHARACTER (LEN = 19) :: time_obs_long
119    INTEGER :: itb, ita
120    INTEGER :: iiunit
121    LOGICAL :: date1_correct, date2_correct
123    IF (PRESENT (iunit)) THEN
124        iiunit = iunit
125    ELSE
126        iiunit = 0
127    ENDIF
129    WRITE (time_obs_long, FMT='(A4,"-",A2,"-",A2,"_",A2,":",A2,":",A2)')    &
130           time_obs ( 1: 4), time_obs ( 5: 6), time_obs ( 7: 8), &
131           time_obs ( 9:10), time_obs (11:12), time_obs (13:14)
133 !  time_obs - Time_window_min (IN >= 0, OUT < 0)
135    CALL GETH_IDTS (time_obs_long, time_window_min, itb, date1_correct, iiunit)
137 !  time_obs - Time_window_max (IN =< 0, OUT > 0)
139    CALL GETH_IDTS (time_obs_long, time_window_max, ita, date2_correct, iiunit)
141    IF (((itb .LT. 0) .OR. (ita .GT. 0)) .OR. &
142        ((.NOT. date1_correct) .OR. (.NOT. date2_correct))) THEN
143        outside_window = .TRUE.              ! Observation out of time window
144    ELSE
145        outside_window = .FALSE.             ! Observation in time window
146    ENDIF
148    RETURN
150 END SUBROUTINE inside_window
152 END MODULE module_inside