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

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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.4 KB
Line 
1! $Header$
2
3SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, lmt_foce, 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, lmt_foce, diff_sst
23
24! Locals variables with attribute SAVE
25!****************************************************************************************
26  REAL, DIMENSION(:), ALLOCATABLE, SAVE :: bils_save, foce_save
27!$OMP THREADPRIVATE(bils_save, foce_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, foce_glo, sst_l_glo, sst_lp1_glo, diff_sst_glo
35  CHARACTER (len = 20)     :: modname = 'limit_slab'
36
37! End declaration
38!****************************************************************************************
39
40  ! calculate number of time steps for one day
41  lmt_pas = NINT(86400./dtime)
42 
43  IF (MOD(itime-1, lmt_pas) == 0) THEN   ! time to read
44     !$OMP MASTER  ! Only master thread
45     IF (is_mpi_root) THEN ! Only master processus
46        print*,'in limit_slab time to read, itime=',itime
47       
48        ierr = NF90_OPEN ('limit_slab.nc', NF90_NOWRITE, nid)
49        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,&
50             'Pb in opening file limit_slab.nc',1)
51       
52        ! La tranche de donnees a lire:
53        start(1) = 1
54        start(2) = jour
55        epais(1) = klon_glo
56        epais(2) = 1
57
58!****************************************************************************************
59! 2) Read bils and ocean fraction
60!
61!****************************************************************************************
62!
63! Read bils_glo
64        ierr = NF90_INQ_VARID(nid, 'BILS_OCE', nvarid)
65        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <BILS_OCE> is abstent',1)
66
67        ierr = NF90_GET_VAR(nid,nvarid,bils_glo,start,epais)
68        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <BILS_OCE> failed',1)
69!
70! Read foce_glo
71        ierr = NF90_INQ_VARID(nid, 'FOCE', nvarid)
72        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <FOCE> is abstent',1)
73
74        ierr = NF90_GET_VAR(nid,nvarid,foce_glo,start,epais)
75        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <FOCE> failed',1)
76!
77! Read sst_glo for this day
78        ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
79        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'The variable <SST> is abstent',1)
80
81        ierr = NF90_GET_VAR(nid,nvarid,sst_l_glo,start,epais)
82        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Reading of <SST> failed',1)
83
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) CALL abort_gcm(modname,'Reading of <SST> day+1 failed',1)
89
90! Calculate difference in temperature between this day and one ahead
91        DO i=1, klon_glo-1
92           diff_sst_glo(i) = sst_lp1_glo(i) - sst_l_glo(i)
93        END DO
94        diff_sst_glo(klon_glo) = sst_lp1_glo(klon_glo) - sst_l_glo(1)
95
96!****************************************************************************************
97! 5) Close file and distribuate variables to all processus
98!
99!****************************************************************************************
100        ierr = NF90_CLOSE(nid)
101        IF (ierr /= NF90_NOERR) CALL abort_gcm(modname,'Pb when closing file', 1)
102     ENDIF ! is_mpi_root
103
104!$OMP END MASTER
105       
106     IF (.NOT. ALLOCATED(bils_save)) THEN
107        ALLOCATE(bils_save(klon), foce_save(klon), stat=ierr)
108        IF (ierr /= 0) CALL abort_gcm('limit_slab', 'pb in allocation',1)
109     END IF
110
111     CALL Scatter(bils_glo, bils_save)
112     CALL Scatter(foce_glo, foce_save)
113     CALL Scatter(diff_sst_glo, diff_sst)
114     
115  ELSE ! not time to read
116     diff_sst(:) = 0.
117  ENDIF ! time to read
118
119  lmt_bils(:) = bils_save(:)
120  lmt_foce(:) = foce_save(:)
121 
122END SUBROUTINE limit_slab
Note: See TracBrowser for help on using the repository browser.