source: trunk/LMDZ.COMMON/libf/evolution/surf_temp.F90 @ 3921

Last change on this file since 3921 was 3907, checked in by jbclement, 5 months ago

PEM:
Correction for the update of surface temperature when ice is disappearing: now it is really set as the surface temperature of the nearest bare soil point because we check the lon-lat grid and not the reduced grid.
JBC

File size: 3.9 KB
Line 
1MODULE surf_temp
2
3implicit none
4
5!=======================================================================
6contains
7!=======================================================================
8
9SUBROUTINE update_tsurf_nearest_baresoil(ngrid,nslope,im,jm,tsurf_avg,co2_ice,is_co2ice_ini,co2ice_disappeared)
10
11implicit none
12
13! Inputs:
14integer,                          intent(in) :: im, jm, nslope, ngrid
15real,    dimension(ngrid,nslope), intent(in) :: co2_ice
16logical, dimension(ngrid,nslope), intent(in) :: is_co2ice_ini
17! Outputs:
18real,    dimension(ngrid,nslope), intent(inout) :: tsurf_avg
19logical, dimension(ngrid,nslope), intent(inout) :: co2ice_disappeared
20! Local variables:
21real, parameter               :: eps = 1.e-10
22integer                       :: islope, i, j, k, radius, rmax, di, dj, ii, jj
23logical                       :: found
24real, dimension(im,jm,nslope) :: tsurf_ll, co2ice_ll, mask_co2ice_ini, co2ice_disappeared_ll
25real, dimension(ngrid)        :: tmp
26
27! Convert from reduced grid to lon-lat grid
28#ifndef CPP_1D
29do islope = 1,nslope
30    call gr_fi_dyn(1,ngrid,im,jm,tsurf_avg(:,islope),tsurf_ll(:,:,islope))
31    call gr_fi_dyn(1,ngrid,im,jm,co2_ice(:,islope),co2ice_ll(:,:,islope))
32    call gr_fi_dyn(1,ngrid,im,jm,merge(1.,0.,is_co2ice_ini(:,islope)),mask_co2ice_ini(:,:,islope))
33    call gr_fi_dyn(1,ngrid,im,jm,merge(1.,0.,co2ice_disappeared(:,islope)),co2ice_disappeared_ll(:,:,islope))
34enddo
35#else
36    tsurf_ll(1,1,:) = tsurf_avg(1,:)
37    co2ice_ll(1,1,:) = co2_ice(1,:)
38    mask_co2ice_ini(1,1,:) = merge(1.,0.,is_co2ice_ini(1,:))
39    co2ice_disappeared_ll(1,1,:) = merge(1.,0.,co2ice_disappeared(1,:))
40#endif
41
42! For each point where ice disappeared
43rmax = max(im,jm)
44do j = 1,jm
45    do i = 1,im
46        do islope = 1,nslope
47            if (mask_co2ice_ini(i,j,islope) > 0.5 .and. co2ice_ll(i,j,islope) < eps .and. co2ice_disappeared_ll(i,j,islope) < 0.5) then
48                found = .false.
49                co2ice_disappeared_ll(i,j,islope) = 1.
50                do k = 1,nslope
51                    if (k /= islope .and. mask_co2ice_ini(i,j,k) < 0.5) then
52                        tsurf_ll(i,j,islope) = tsurf_ll(i,j,k)
53                        found = .true.
54                        exit
55                    endif
56                enddo
57
58                radius = 1
59                do while (.not. found .and. radius <= rmax) ! only if no adjacent slopes holds bare soil
60                    do dj = -radius,radius
61                        do di = -radius,radius
62                            if (abs(di) + abs(dj) == radius) then
63                                ii = i + di
64                                jj = j + dj
65                                if (ii >= 1 .and. ii <= im .and. jj >= 1 .and. jj <= jm) then
66                                    do k = 1,nslope
67                                        if (mask_co2ice_ini(ii,jj,k) < 0.5) then
68                                            tsurf_ll(i,j,islope) = tsurf_ll(i,j,k)
69                                            found = .true.
70                                            exit
71                                        endif
72                                    enddo
73                                endif
74                            endif
75                            if (found) exit
76                        enddo
77                        if (found) exit
78                    enddo
79                    radius = radius + 1
80                enddo
81            endif
82
83        enddo
84    enddo
85enddo
86
87! Convert back from lon-lat grid to reduced grid
88#ifndef CPP_1D
89do islope = 1,nslope
90    call gr_dyn_fi(1,im,jm,ngrid,tsurf_ll(:,:,islope),tsurf_avg(:,islope))
91    call gr_dyn_fi(1,im,jm,ngrid,co2ice_disappeared_ll(:,:,islope),tmp)
92    where (tmp > 0.5) co2ice_disappeared(:,islope) = .true.
93enddo
94#else
95    tsurf_avg(1,:) = tsurf_ll(1,1,:)
96    where(co2ice_disappeared_ll(1,1,:) > 0.5) co2ice_disappeared(1,:) = .true.
97#endif
98
99END SUBROUTINE update_tsurf_nearest_baresoil
100
101END MODULE surf_temp
Note: See TracBrowser for help on using the repository browser.