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

Last change on this file since 3961 was 3933, checked in by jbclement, 4 weeks ago

PEM:
Correction on dimensions for the new algoirthm introduced in r3907 to update of surface temperatue when ice disappeared.
JBC

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