source: LMDZ5/trunk/libf/phylmd/limit_slab.F90 @ 2209

Last change on this file since 2209 was 2209, checked in by Ehouarn Millour, 9 years ago

Update of the slab ocean by Francis Codron. There are now 3 possibilities for the "version_ocean" slab type:
sicOBS = prescribed ice fraction. Water temperature nearby is set to -1.8°C and cannot become lower.
sicNO = ignore sea ice. One can prescribe a fraction, but the nearby ocean evolves freely, depending on surface fluxes: temperature can go below freezing point or above...
sicINT = interactive sea ice.
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 5.5 KB
Line 
1! $Header$
2
3SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, diff_sst, diff_siv)
4
5  USE dimphy
6  USE mod_grid_phy_lmdz
7  USE mod_phys_lmdz_para
8  USE netcdf
9  USE indice_sol_mod
10
11  IMPLICIT NONE
12
13  INCLUDE "temps.h"
14  INCLUDE "clesphys.h"
15  INCLUDE "dimensions.h"
16
17! In- and ouput arguments
18!****************************************************************************************
19  INTEGER, INTENT(IN) :: itime   ! numero du pas de temps courant
20  INTEGER, INTENT(IN) :: jour    ! jour a lire dans l'annee
21  REAL   , INTENT(IN) :: dtime   ! pas de temps de la physique (en s)
22  REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils, diff_sst, diff_siv
23
24! Locals variables with attribute SAVE
25!****************************************************************************************
26  REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, diff_sst_save
27  REAL, DIMENSION(:), ALLOCATABLE, SAVE :: diff_siv_save
28!$OMP THREADPRIVATE(bils_save, diff_sst_save, diff_siv_save)
29
30! Locals variables
31!****************************************************************************************
32  INTEGER                  :: lmt_pas   
33  INTEGER                  :: nvarid, nid, ierr, i
34  INTEGER, DIMENSION(2)    :: start, epais
35  REAL, DIMENSION(klon_glo):: bils_glo, sst_l_glo, sst_lp1_glo, diff_sst_glo
36  REAL, DIMENSION(klon_glo):: siv_l_glo, siv_lp1_glo, diff_siv_glo
37  CHARACTER (len = 20)     :: modname = 'limit_slab'
38  LOGICAL                  :: read_bils,read_sst,read_siv
39
40! End declaration
41!****************************************************************************************
42
43  ! calculate number of time steps for one day
44  lmt_pas = NINT(86400./dtime)
45 
46  ! F. Codron 5/14: add defaults for bils, diff_sst (0)
47  IF (MOD(itime-1, lmt_pas) == 0) THEN   ! time to read
48     !$OMP MASTER  ! Only master thread
49     IF (is_mpi_root) THEN ! Only master processus
50        print*,'in limit_slab time to read, itime=',itime
51        read_bils=.TRUE.
52        read_sst=.TRUE.
53        read_siv=.TRUE.
54       
55        ierr = NF90_OPEN ('limit_slab.nc', NF90_NOWRITE, nid)
56        IF (ierr /= NF90_NOERR) THEN
57            read_bils=.FALSE.
58            read_sst=.FALSE.
59            read_siv=.FALSE.
60        ELSE ! read file
61       
62        ! La tranche de donnees a lire:
63        start(1) = 1
64        start(2) = jour
65        epais(1) = klon_glo
66        epais(2) = 1
67
68!****************************************************************************************
69! 2) Read bils and SST/ ice volume tendency
70!
71!****************************************************************************************
72!
73! Read bils_glo
74        ierr = NF90_INQ_VARID(nid, 'BILS_OCE', nvarid)
75        IF (ierr /= NF90_NOERR) THEN
76            read_bils=.FALSE.
77        ELSE
78            ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais)
79            IF (ierr /= NF90_NOERR) read_bils=.FALSE.
80        END IF
81! Read sst_glo for this day
82        ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
83        IF (ierr /= NF90_NOERR)  THEN
84            read_sst=.FALSE.
85        ELSE
86            ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)
87            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
88! Read sst_glo for one day ahead
89            start(2) = jour + 1
90            IF (start(2) > 360) start(2)=1
91            ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais)
92            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
93        END IF
94
95! Read siv_glo for this day
96        ierr = NF90_INQ_VARID(nid, 'SICV', nvarid)
97        IF (ierr /= NF90_NOERR)  THEN
98            read_siv=.FALSE.
99        ELSE
100            start(2) = jour
101            ierr = NF90_GET_VAR(nid,nvarid,siv_l_glo,start,epais)
102            IF (ierr /= NF90_NOERR) read_siv=.FALSE.
103! Read siv_glo for one day ahead
104            start(2) = jour + 1
105            IF (start(2) > 360) start(2)=1
106            ierr = NF90_GET_VAR(nid,nvarid,siv_lp1_glo,start,epais)
107            IF (ierr /= NF90_NOERR) read_siv=.FALSE.
108        END IF
109
110!****************************************************************************************
111! 5) Close file and distribute variables to all processus
112!
113!****************************************************************************************
114        ierr = NF90_CLOSE(nid)
115        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
116        END IF ! Read File
117        IF (read_sst) THEN
118! Calculate difference in temperature between this day and one ahead
119            DO i=1, klon_glo
120               diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
121            END DO
122        END IF !read_sst
123        IF (read_siv) THEN
124! Calculate difference in temperature between this day and one ahead
125            DO i=1, klon_glo
126               diff_siv_glo(i) = siv_lp1_glo(i) - siv_l_glo(i)
127            END DO
128        END IF !read_siv
129     ENDIF ! is_mpi_root
130
131!$OMP END MASTER
132       
133     IF (.NOT. ALLOCATED(bils_save)) THEN
134        ALLOCATE(bils_save(klon), diff_sst_save(klon), diff_siv_save(klon), stat=ierr)
135        IF (ierr /= 0) CALL abort_gcm('limit_slab', 'pb in allocation',1)
136     END IF
137
138! Give default values if needed
139     IF (read_bils) THEN
140         CALL Scatter(bils_glo, bils_save)
141     ELSE
142         bils_save(:)=0.
143     END IF
144     IF (read_sst) THEN
145         CALL Scatter(diff_sst_glo, diff_sst_save)
146     ELSE
147         diff_sst_save(:)=0.
148     END IF
149     IF (read_siv) THEN
150         CALL Scatter(diff_siv_glo, diff_siv_save)
151     ELSE
152         diff_siv_save(:)=0.
153     END IF
154     
155  ENDIF ! time to read
156
157  lmt_bils(:) = bils_save(:)
158  diff_sst(:) = diff_sst_save(:)
159  diff_siv(:) = diff_siv_save(:)
160
161 
162END SUBROUTINE limit_slab
Note: See TracBrowser for help on using the repository browser.