source: LMDZ4/trunk/libf/phylmd/limit_slab.F90 @ 996

Last change on this file since 996 was 996, checked in by lsce, 16 years ago
  • Modifications liées au calcul des nouveau sous-fractions
  • Nettoyage de ocean slab : il reste uniquement la version avec glace de mer forcé
  • Nouveaux variables pour distiguer la version et type d'ocean : type_ocean=force/slab/couple, version_ocean=opa8/nemo pour couplé ou version_ocean=sicOBS pour slab

JG

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