source: LMDZ5/trunk/libf/dyn3d/fluxstokenc.F @ 2600

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

Cleanup in the dynamics: turn comvert.h into module comvert_mod.F90
EM

  • 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:keywords set to Author Date Id Revision
File size: 4.3 KB
Line 
1!
2! $Id: fluxstokenc.F 2600 2016-07-23 05:45:38Z emillour $
3!
4      SUBROUTINE fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
5     . time_step,itau )
6#ifdef CPP_IOIPSL
7! This routine is designed to work with ioipsl
8
9       USE IOIPSL
10c
11c     Auteur :  F. Hourdin
12c
13c
14ccc   ..   Modif. P. Le Van  ( 20/12/97 )  ...
15c
16      IMPLICIT NONE
17c
18      include "dimensions.h"
19      include "paramet.h"
20      include "comgeom.h"
21      include "tracstoke.h"
22      include "temps.h"
23      include "iniprint.h"
24
25      REAL time_step,t_wrt, t_ops
26      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)
27      REAL masse(ip1jmp1,llm),teta(ip1jmp1,llm),phi(ip1jmp1,llm)
28      REAL phis(ip1jmp1)
29
30      REAL pbaruc(ip1jmp1,llm),pbarvc(ip1jm,llm)
31      REAL massem(ip1jmp1,llm),tetac(ip1jmp1,llm),phic(ip1jmp1,llm)
32
33      REAL pbarug(ip1jmp1,llm),pbarvg(iip1,jjm,llm),wg(ip1jmp1,llm)
34
35      REAL pbarvst(iip1,jjp1,llm),zistdyn
36        real dtcum
37
38      INTEGER iadvtr,ndex(1)
39      integer nscal
40      real tst(1),ist(1),istp(1)
41      INTEGER ij,l,irec,i,j,itau
42      INTEGER, SAVE :: fluxid, fluxvid,fluxdid
43 
44      SAVE iadvtr, massem,pbaruc,pbarvc,irec
45      SAVE phic,tetac
46      logical first
47      save first
48      data first/.true./
49      DATA iadvtr/0/
50
51
52c AC initialisations
53      pbarug(:,:)   = 0.
54      pbarvg(:,:,:) = 0.
55      wg(:,:)       = 0.
56     
57
58      if(first) then
59
60        CALL initfluxsto( 'fluxstoke',
61     .  time_step,istdyn* time_step,istdyn* time_step,
62     .  fluxid,fluxvid,fluxdid)
63       
64        ndex(1) = 0
65        call histwrite(fluxid, 'phis', 1, phis, iip1*jjp1, ndex)
66        call histwrite(fluxid, 'aire', 1, aire, iip1*jjp1, ndex)
67       
68        ndex(1) = 0
69        nscal = 1
70        tst(1) = time_step
71        call histwrite(fluxdid, 'dtvr', 1, tst, nscal, ndex)
72        ist(1)=istdyn
73        call histwrite(fluxdid, 'istdyn', 1, ist, nscal, ndex)
74        istp(1)= istphy
75        call histwrite(fluxdid, 'istphy', 1, istp, nscal, ndex)
76       
77        first = .false.
78
79      endif
80
81
82      IF(iadvtr.EQ.0) THEN
83         phic(:,:)=0
84         tetac(:,:)=0
85         pbaruc(:,:)=0
86         pbarvc(:,:)=0
87      ENDIF
88
89c   accumulation des flux de masse horizontaux
90      DO l=1,llm
91         DO ij = 1,ip1jmp1
92            pbaruc(ij,l) = pbaruc(ij,l) + pbaru(ij,l)
93            tetac(ij,l) = tetac(ij,l) + teta(ij,l)
94            phic(ij,l) = phic(ij,l) + phi(ij,l)
95         ENDDO
96         DO ij = 1,ip1jm
97            pbarvc(ij,l) = pbarvc(ij,l) + pbarv(ij,l)
98         ENDDO
99      ENDDO
100
101c   selection de la masse instantannee des mailles avant le transport.
102      IF(iadvtr.EQ.0) THEN
103         CALL SCOPY(ip1jmp1*llm,masse,1,massem,1)
104      ENDIF
105
106      iadvtr   = iadvtr+1
107
108
109c   Test pour savoir si on advecte a ce pas de temps
110      IF ( iadvtr.EQ.istdyn ) THEN
111c    normalisation
112      DO l=1,llm
113         DO ij = 1,ip1jmp1
114            pbaruc(ij,l) = pbaruc(ij,l)/REAL(istdyn)
115            tetac(ij,l) = tetac(ij,l)/REAL(istdyn)
116            phic(ij,l) = phic(ij,l)/REAL(istdyn)
117         ENDDO
118         DO ij = 1,ip1jm
119            pbarvc(ij,l) = pbarvc(ij,l)/REAL(istdyn)
120         ENDDO
121      ENDDO
122
123c   traitement des flux de masse avant advection.
124c     1. calcul de w
125c     2. groupement des mailles pres du pole.
126
127        CALL groupe( massem, pbaruc,pbarvc, pbarug,pbarvg,wg )
128
129        do l=1,llm
130           do j=1,jjm
131              do i=1,iip1
132                 pbarvst(i,j,l)=pbarvg(i,j,l)
133              enddo
134           enddo
135           do i=1,iip1
136              pbarvst(i,jjp1,l)=0.
137           enddo
138        enddo
139
140         iadvtr=0
141        write(lunout,*)'ITAU auquel on stoke les fluxmasses',itau
142       
143        call histwrite(fluxid, 'masse', itau, massem,
144     .               iip1*jjp1*llm, ndex)
145       
146        call histwrite(fluxid, 'pbaru', itau, pbarug,
147     .               iip1*jjp1*llm, ndex)
148       
149        call histwrite(fluxvid, 'pbarv', itau, pbarvg,
150     .               iip1*jjm*llm, ndex)
151       
152        call histwrite(fluxid, 'w' ,itau, wg,
153     .             iip1*jjp1*llm, ndex)
154       
155        call histwrite(fluxid, 'teta' ,itau, tetac,
156     .             iip1*jjp1*llm, ndex)
157       
158        call histwrite(fluxid, 'phi' ,itau, phic,
159     .             iip1*jjp1*llm, ndex)
160       
161C
162
163      ENDIF ! if iadvtr.EQ.istdyn
164
165#else
166      write(lunout,*)
167     & 'fluxstokenc: Needs IOIPSL to function'
168#endif
169! of #ifdef CPP_IOIPSL
170      RETURN
171      END
Note: See TracBrowser for help on using the repository browser.