1 MODULE module_positive_definite
3 USE module_wrf_error ! frame
7 SUBROUTINE positive_definite_slab( f, &
8 ids, ide, jds, jde, kds, kde, &
9 ims, ime, jms, jme, kms, kme, &
10 its, ite, jts, jte, kts, kte)
15 INTEGER, INTENT(IN ) :: ids, ide, jds, jde, kds, kde, &
16 ims, ime, jms, jme, kms, kme, &
17 its, ite, jts, jte, kts, kte
18 REAL, DIMENSION( ims:ime, kms:kme, jms:jme ), INTENT(INOUT) :: f
21 REAL, DIMENSION(:), ALLOCATABLE :: line
22 INTEGER :: j, k, i_end, j_end, k_end
23 REAL :: fmin, ftotal_pre, rftotal_post
25 ! Initialize variables
27 j_end = MIN(jte, jde-1)
29 ! Only do anything if we have to...
30 IF (ANY(f(ids:i_end,kts:k_end,jts:j_end) < 0.)) THEN
31 ! number of points in the X direction, not including U-stagger
32 ALLOCATE(line(ide-ids))
35 !while_lt_0_loop: DO WHILE (ANY(f(ids:i_end,k,j) < 0.))
36 f_lt_0: IF (ANY(f(ids:i_end,k,j) < 0.)) THEN
37 line(:) = f(ids:i_end,k,j)
38 ! This is actually an integration over x assuming dx is constant
39 ftotal_pre = SUM(line)
40 ! If the total is negative, set everything to 0. and exit
41 IF (ftotal_pre < 0.) THEN
44 ! Value to add to array to make sure every element is > 0.
46 line(:) = line(:) - fmin ! fmin is negative...
47 rftotal_post = 1./SUM(line)
48 line = line*ftotal_pre*rftotal_post
49 ! The following error can naturally occur on 32-bit machines:
50 !IF (SUM(line) /= ftotal_pre) THEN
51 ! write(wrf_err_message,*) 'ERROR: module_positive_definite, ',&
52 ! 'mismatching sums ',j,k,ftotal_pre,&
53 ! SUM(line),fmin,1./rftotal_post
55 ! CALL wrf_error_fatal( wrf_err_message )
58 f(ids:i_end,k,j) = line(:)
60 !END DO while_lt_0_loop
66 END SUBROUTINE positive_definite_slab
68 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
70 SUBROUTINE positive_definite_sheet( f, f_total, nx, ny )
75 INTEGER, INTENT(IN ) :: nx, ny
76 REAL, DIMENSION( nx, ny ), INTENT(INOUT) :: f
77 REAL, DIMENSION( ny ), INTENT(IN) :: f_total
80 REAL, DIMENSION(:), ALLOCATABLE :: line
82 REAL :: fmin, rftotal_post, sum_line
83 REAL, PARAMETER :: eps = 1.0e-15
85 ! Only do anything if we have to...
89 !while_lt_0_loop: DO WHILE (ANY(f(:,iy) < 0.))
90 f_lt_0: IF (ANY(f(:,iy) < 0.)) THEN
92 ! If the total is negative, set everything to 0. and exit
93 IF (f_total(iy) < 0.) THEN
96 ! Value to add to array to make sure every element is > 0.
98 line(:) = line(:) - fmin ! fmin is negative...
100 IF(sum_line > eps) THEN
101 rftotal_post = 1./sum_line
102 line = line*f_total(iy)*rftotal_post
106 ! The following error can naturally occur on 32-bit machines:
107 !IF (SUM(line) /= f_total(iy)) THEN
108 ! write(wrf_err_message,*) 'ERROR: module_positive_definite, ',&
109 ! 'mismatching sums ',iy,f_total(iy), &
110 ! SUM(line),fmin,1./rftotal_post
112 ! CALL wrf_error_fatal( wrf_err_message )
117 !END DO while_lt_0_loop
122 END SUBROUTINE positive_definite_sheet
124 END MODULE module_positive_definite