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

Last change on this file since 2057 was 2057, checked in by Ehouarn Millour, 10 years ago

Preparatory stuff to fix and improve the slab ocean model.
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: 4.5 KB
Line 
1! $Header$
2
3SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, diff_sst)
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
23
24! Locals variables with attribute SAVE
25!****************************************************************************************
26  REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, diff_sst_save
27!$OMP THREADPRIVATE(bils_save, diff_sst_save)
28
29! Locals variables
30!****************************************************************************************
31  INTEGER                  :: lmt_pas   
32  INTEGER                  :: nvarid, nid, ierr, i
33  INTEGER, DIMENSION(2)    :: start, epais
34  REAL, DIMENSION(klon_glo):: bils_glo, sst_l_glo, sst_lp1_glo, diff_sst_glo
35  CHARACTER (len = 20)     :: modname = 'limit_slab'
36  LOGICAL                  :: read_bils,read_sst
37
38! End declaration
39!****************************************************************************************
40
41  ! calculate number of time steps for one day
42  lmt_pas = NINT(86400./dtime)
43 
44  ! F. Codron 5/14: add defaults for bils, diff_sst (0)
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
49        read_bils=.TRUE.
50        read_sst=.TRUE.
51       
52        ierr = NF90_OPEN ('limit_slab.nc', NF90_NOWRITE, nid)
53        IF (ierr /= NF90_NOERR) THEN
54            read_bils=.FALSE.
55            read_sst=.FALSE.
56        ELSE ! read file
57       
58        ! La tranche de donnees a lire:
59        start(1) = 1
60        start(2) = jour
61        epais(1) = klon_glo
62        epais(2) = 1
63
64!****************************************************************************************
65! 2) Read bils and SST tendency
66!
67!****************************************************************************************
68!
69! Read bils_glo
70        ierr = NF90_INQ_VARID(nid, 'BILS_OCE', nvarid)
71        IF (ierr /= NF90_NOERR) THEN
72            read_bils=.FALSE.
73        ELSE
74            ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais)
75            IF (ierr /= NF90_NOERR) read_bils=.FALSE.
76        END IF
77! Read sst_glo for this day
78        ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
79        IF (ierr /= NF90_NOERR)  THEN
80            read_sst=.FALSE.
81        ELSE
82            ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)
83            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
84! Read sst_glo for one day ahead
85            start(2) = jour + 1
86            IF (start(2) > 360) start(2)=1
87            ierr = NF90_GET_VAR(nid,nvarid,sst_lp1_glo,start,epais)
88            IF (ierr /= NF90_NOERR) read_sst=.FALSE.
89        END IF
90
91!****************************************************************************************
92! 5) Close file and distribute variables to all processus
93!
94!****************************************************************************************
95        ierr = NF90_CLOSE(nid)
96        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
97        END IF ! Read File
98        IF (read_sst) THEN
99! Calculate difference in temperature between this day and one ahead
100!            DO i=1, klon_glo-1
101!               diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
102!            END DO
103!            diff_sst_glo(klon_glo) = sst_lp1_glo(klon_glo) - sst_l_glo(1)
104            DO i=1, klon_glo
105               diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
106            END DO
107        END IF !read_sst
108     ENDIF ! is_mpi_root
109
110!$OMP END MASTER
111       
112     IF (.NOT. ALLOCATED(bils_save)) THEN
113        ALLOCATE(bils_save(klon), diff_sst_save(klon), stat=ierr)
114        IF (ierr /= 0) CALL abort_gcm('limit_slab', 'pb in allocation',1)
115     END IF
116
117! Giveddefault values if needed
118     IF (read_bils) THEN
119         CALL Scatter(bils_glo, bils_save)
120     ELSE
121         bils_save(:)=0.
122     END IF
123     IF (read_sst) THEN
124         CALL Scatter(diff_sst_glo, diff_sst_save)
125     ELSE
126         diff_sst_save(:)=0.
127     END IF
128     
129  ENDIF ! time to read
130
131  lmt_bils(:) = bils_save(:)
132  diff_sst(:) = diff_sst_save(:)
133 
134END SUBROUTINE limit_slab
Note: See TracBrowser for help on using the repository browser.