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

Last change on this file since 3977 was 3977, checked in by jbclement, 4 days ago

PEM:

  • All operations computed by the PEM on the PCM data (averages, minima) are now performed by XIOS with two dedicated file. One is for daily operation outputs ("Xoutdaily4pem*.nc") and the other for yearly operation outputs ("Xoutyearly4pem*.nc").
  • Deletion of the reshaping tool "reshape_XIOS_output" used to convert XIOS outputs onto the PCM grid. Thus, the PEM is now able to read directly the format of XIOS outputs.
  • Addition of subroutines to convert data between a lon x lat array and a vector.

JBC

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