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

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

Physics/dynamics separation: get rid of all the 'include "temps.h"' in the physics; variables in module time_phylmdz_mod must be used instead. Also added JD_cur, JH_cur and JD_ref in module phys_cal_mod, in preparation for having physics handle its calendar internally.
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
RevLine 
[996]1! $Header$
2
[2209]3SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, diff_sst, diff_siv)
[996]4
5  USE dimphy
[2344]6  USE mod_grid_phy_lmdz, ONLY: klon_glo
[996]7  USE mod_phys_lmdz_para
8  USE netcdf
[1785]9  USE indice_sol_mod
[996]10
11  IMPLICIT NONE
12
13  INCLUDE "clesphys.h"
14
15! In- and ouput arguments
16!****************************************************************************************
17  INTEGER, INTENT(IN) :: itime   ! numero du pas de temps courant
18  INTEGER, INTENT(IN) :: jour    ! jour a lire dans l'annee
19  REAL   , INTENT(IN) :: dtime   ! pas de temps de la physique (en s)
[2209]20  REAL, DIMENSION(klon), INTENT(OUT) :: lmt_bils, diff_sst, diff_siv
[996]21
22! Locals variables with attribute SAVE
23!****************************************************************************************
[2057]24  REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, diff_sst_save
[2209]25  REAL, DIMENSION(:), ALLOCATABLE, SAVE :: diff_siv_save
26!$OMP THREADPRIVATE(bils_save, diff_sst_save, diff_siv_save)
[996]27
28! Locals variables
29!****************************************************************************************
30  INTEGER                  :: lmt_pas   
31  INTEGER                  :: nvarid, nid, ierr, i
32  INTEGER, DIMENSION(2)    :: start, epais
[2057]33  REAL, DIMENSION(klon_glo):: bils_glo, sst_l_glo, sst_lp1_glo, diff_sst_glo
[2209]34  REAL, DIMENSION(klon_glo):: siv_l_glo, siv_lp1_glo, diff_siv_glo
[996]35  CHARACTER (len = 20)     :: modname = 'limit_slab'
[2209]36  LOGICAL                  :: read_bils,read_sst,read_siv
[996]37
38! End declaration
39!****************************************************************************************
40
41  ! calculate number of time steps for one day
42  lmt_pas = NINT(86400./dtime)
43 
[2057]44  ! F. Codron 5/14: add defaults for bils, diff_sst (0)
[996]45  IF (MOD(itime-1, lmt_pas) == 0) THEN   ! time to read
46     !$OMP MASTER  ! Only master thread
47     IF (is_mpi_root) THEN ! Only master processus
48        print*,'in limit_slab time to read, itime=',itime
[2057]49        read_bils=.TRUE.
50        read_sst=.TRUE.
[2209]51        read_siv=.TRUE.
[996]52       
53        ierr = NF90_OPEN ('limit_slab.nc', NF90_NOWRITE, nid)
[2057]54        IF (ierr /= NF90_NOERR) THEN
55            read_bils=.FALSE.
56            read_sst=.FALSE.
[2209]57            read_siv=.FALSE.
[2057]58        ELSE ! read file
[996]59       
60        ! La tranche de donnees a lire:
61        start(1) = 1
62        start(2) = jour
63        epais(1) = klon_glo
64        epais(2) = 1
65
66!****************************************************************************************
[2209]67! 2) Read bils and SST/ ice volume tendency
[996]68!
69!****************************************************************************************
70!
71! Read bils_glo
72        ierr = NF90_INQ_VARID(nid, 'BILS_OCE', nvarid)
[2057]73        IF (ierr /= NF90_NOERR) THEN
74            read_bils=.FALSE.
75        ELSE
76            ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais)
77            IF (ierr /= NF90_NOERR) read_bils=.FALSE.
78        END IF
[996]79! Read sst_glo for this day
80        ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
[2057]81        IF (ierr /= NF90_NOERR)  THEN
82            read_sst=.FALSE.
83        ELSE
84            ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)
85            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
[996]86! Read sst_glo for one day ahead
[2057]87            start(2) = jour + 1
88            IF (start(2) > 360) start(2)=1
89            ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais)
90            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
91        END IF
[996]92
[2209]93! Read siv_glo for this day
94        ierr = NF90_INQ_VARID(nid, 'SICV', nvarid)
95        IF (ierr /= NF90_NOERR)  THEN
96            read_siv=.FALSE.
97        ELSE
98            start(2) = jour
99            ierr = NF90_GET_VAR(nid,nvarid,siv_l_glo,start,epais)
100            IF (ierr /= NF90_NOERR) read_siv=.FALSE.
101! Read siv_glo for one day ahead
102            start(2) = jour + 1
103            IF (start(2) > 360) start(2)=1
104            ierr = NF90_GET_VAR(nid,nvarid,siv_lp1_glo,start,epais)
105            IF (ierr /= NF90_NOERR) read_siv=.FALSE.
106        END IF
107
[996]108!****************************************************************************************
[2057]109! 5) Close file and distribute variables to all processus
[996]110!
111!****************************************************************************************
112        ierr = NF90_CLOSE(nid)
[2311]113        IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
[2057]114        END IF ! Read File
115        IF (read_sst) THEN
116! Calculate difference in temperature between this day and one ahead
117            DO i=1, klon_glo
118               diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
119            END DO
120        END IF !read_sst
[2209]121        IF (read_siv) THEN
122! Calculate difference in temperature between this day and one ahead
123            DO i=1, klon_glo
124               diff_siv_glo(i) = siv_lp1_glo(i) - siv_l_glo(i)
125            END DO
126        END IF !read_siv
[996]127     ENDIF ! is_mpi_root
128
129!$OMP END MASTER
130       
131     IF (.NOT. ALLOCATED(bils_save)) THEN
[2209]132        ALLOCATE(bils_save(klon), diff_sst_save(klon), diff_siv_save(klon), stat=ierr)
[2311]133        IF (ierr /= 0) CALL abort_physic('limit_slab', 'pb in allocation',1)
[996]134     END IF
135
[2209]136! Give default values if needed
[2057]137     IF (read_bils) THEN
138         CALL Scatter(bils_glo, bils_save)
139     ELSE
140         bils_save(:)=0.
141     END IF
142     IF (read_sst) THEN
143         CALL Scatter(diff_sst_glo, diff_sst_save)
144     ELSE
145         diff_sst_save(:)=0.
146     END IF
[2209]147     IF (read_siv) THEN
148         CALL Scatter(diff_siv_glo, diff_siv_save)
149     ELSE
150         diff_siv_save(:)=0.
151     END IF
[996]152     
153  ENDIF ! time to read
154
155  lmt_bils(:) = bils_save(:)
[2057]156  diff_sst(:) = diff_sst_save(:)
[2209]157  diff_siv(:) = diff_siv_save(:)
158
[996]159 
160END SUBROUTINE limit_slab
Note: See TracBrowser for help on using the repository browser.