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

Last change on this file since 2934 was 2656, checked in by Ehouarn Millour, 8 years ago

Making the slab work:

  • added a slab_heat_transp_mod module for horizontal diffusion and Ekman transport
  • added storage and output of relevent variables in phyredem, phyetat0, phy_output_ctrlout_mod, phys_output_write_mod
  • moved nslay (number of slab layers) out of dimphy into ocean_slab_mod.

FC

  • 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.7 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 
[2514]44! Initialize saved variables
45     IF (.NOT. ALLOCATED(bils_save)) THEN
46        ALLOCATE(bils_save(klon), diff_sst_save(klon), diff_siv_save(klon), stat=ierr)
47        IF (ierr /= 0) CALL abort_physic('limit_slab', 'pb in allocation',1)
48     END IF
49
[2057]50  ! F. Codron 5/14: add defaults for bils, diff_sst (0)
[996]51  IF (MOD(itime-1, lmt_pas) == 0) THEN   ! time to read
[2514]52!$OMP MASTER  ! Only master thread
[996]53     IF (is_mpi_root) THEN ! Only master processus
54        print*,'in limit_slab time to read, itime=',itime
[2057]55        read_bils=.TRUE.
56        read_sst=.TRUE.
[2209]57        read_siv=.TRUE.
[996]58       
59        ierr = NF90_OPEN ('limit_slab.nc', NF90_NOWRITE, nid)
[2057]60        IF (ierr /= NF90_NOERR) THEN
[2514]61            PRINT *,'LIMIT_SLAB file not found'
[2057]62            read_bils=.FALSE.
63            read_sst=.FALSE.
[2209]64            read_siv=.FALSE.
[2057]65        ELSE ! read file
[996]66       
67        ! La tranche de donnees a lire:
68        start(1) = 1
69        start(2) = jour
70        epais(1) = klon_glo
71        epais(2) = 1
72
73!****************************************************************************************
[2209]74! 2) Read bils and SST/ ice volume tendency
[996]75!
76!****************************************************************************************
77!
78! Read bils_glo
79        ierr = NF90_INQ_VARID(nid, 'BILS_OCE', nvarid)
[2057]80        IF (ierr /= NF90_NOERR) THEN
81            read_bils=.FALSE.
82        ELSE
83            ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais)
84            IF (ierr /= NF90_NOERR) read_bils=.FALSE.
85        END IF
[996]86! Read sst_glo for this day
87        ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
[2057]88        IF (ierr /= NF90_NOERR)  THEN
89            read_sst=.FALSE.
90        ELSE
91            ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)
92            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
[996]93! Read sst_glo for one day ahead
[2057]94            start(2) = jour + 1
95            IF (start(2) > 360) start(2)=1
96            ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais)
97            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
98        END IF
[996]99
[2209]100! Read siv_glo for this day
101        ierr = NF90_INQ_VARID(nid, 'SICV', nvarid)
102        IF (ierr /= NF90_NOERR)  THEN
103            read_siv=.FALSE.
104        ELSE
105            start(2) = jour
106            ierr = NF90_GET_VAR(nid,nvarid,siv_l_glo,start,epais)
107            IF (ierr /= NF90_NOERR) read_siv=.FALSE.
108! Read siv_glo for one day ahead
109            start(2) = jour + 1
110            IF (start(2) > 360) start(2)=1
111            ierr = NF90_GET_VAR(nid,nvarid,siv_lp1_glo,start,epais)
112            IF (ierr /= NF90_NOERR) read_siv=.FALSE.
113        END IF
114
[996]115!****************************************************************************************
[2057]116! 5) Close file and distribute variables to all processus
[996]117!
118!****************************************************************************************
119        ierr = NF90_CLOSE(nid)
[2311]120        IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
[2514]121        END IF ! Read File
[2057]122        IF (read_sst) THEN
123! Calculate difference in temperature between this day and one ahead
124            DO i=1, klon_glo
125               diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
126            END DO
127        END IF !read_sst
[2209]128        IF (read_siv) THEN
129! Calculate difference in temperature between this day and one ahead
130            DO i=1, klon_glo
131               diff_siv_glo(i) = siv_lp1_glo(i) - siv_l_glo(i)
132            END DO
133        END IF !read_siv
[996]134     ENDIF ! is_mpi_root
135
136!$OMP END MASTER
[2514]137!$OMP BARRIER
[996]138       
[2514]139! Send fields to all processes
[2209]140! Give default values if needed
[2514]141     CALL bcast(read_bils)
142     CALL bcast(read_sst)
143     CALL bcast(read_siv)
144     PRINT *,'limit_slab sst',read_sst,'siv',read_siv,'qflux',read_bils
[2057]145     IF (read_bils) THEN
146         CALL Scatter(bils_glo, bils_save)
147     ELSE
148         bils_save(:)=0.
149     END IF
150     IF (read_sst) THEN
151         CALL Scatter(diff_sst_glo, diff_sst_save)
152     ELSE
153         diff_sst_save(:)=0.
154     END IF
[2209]155     IF (read_siv) THEN
156         CALL Scatter(diff_siv_glo, diff_siv_save)
157     ELSE
158         diff_siv_save(:)=0.
159     END IF
[996]160     
161  ENDIF ! time to read
162
163  lmt_bils(:) = bils_save(:)
[2057]164  diff_sst(:) = diff_sst_save(:)
[2209]165  diff_siv(:) = diff_siv_save(:)
166
[996]167END SUBROUTINE limit_slab
Note: See TracBrowser for help on using the repository browser.