My Project
 All Classes Files Functions Variables Macros
limit_slab.F90
Go to the documentation of this file.
1 ! $Header$
2 
3 SUBROUTINE limit_slab(itime, dtime, jour, lmt_bils, lmt_foce, diff_sst)
4 
5  USE dimphy
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 !$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 
122 END SUBROUTINE limit_slab