/[lmdze]/trunk/dyn3d/fluxstokenc.f
ViewVC logotype

Diff of /trunk/dyn3d/fluxstokenc.f

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/dyn3d/fluxstokenc.f revision 27 by guez, Thu Mar 25 14:29:07 2010 UTC trunk/libf/dyn3d/fluxstokenc.f90 revision 31 by guez, Thu Apr 1 14:59:19 2010 UTC
# Line 1  Line 1 
1        SUBROUTINE fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,  SUBROUTINE fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, time_step, itau)
      . time_step,itau )  
2    
3         USE IOIPSL    ! Author: F. Hourdin
 c  
 c     Auteur :  F. Hourdin  
 c  
 c  
 ccc   ..   Modif. P. Le Van  ( 20/12/97 )  ...  
 c  
       use dimens_m  
       use paramet_m  
       use comconst  
       use comvert  
       use comgeom  
       use temps  
       use tracstoke  
       IMPLICIT NONE  
 c  
   
       REAL time_step,t_wrt, t_ops  
       REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)  
       REAL masse(ip1jmp1,llm),teta(ip1jmp1,llm),phi(ip1jmp1,llm)  
       REAL phis(ip1jmp1)  
   
       REAL pbaruc(ip1jmp1,llm),pbarvc(ip1jm,llm)  
       REAL massem(ip1jmp1,llm),tetac(ip1jmp1,llm),phic(ip1jmp1,llm)  
   
       REAL pbarug(ip1jmp1,llm),pbarvg(iip1,jjm,llm),wg(ip1jmp1,llm)  
   
       REAL pbarvst(iip1,jjp1,llm),zistdyn  
         real dtcum  
   
       INTEGER iadvtr,ndex(1)  
       integer nscal  
       real tst(1),ist(1),istp(1)  
       INTEGER ij,l,irec,i,j  
       integer, intent(in):: itau  
       INTEGER fluxid, fluxvid,fluxdid  
   
       SAVE iadvtr, massem,pbaruc,pbarvc,irec  
       SAVE phic,tetac  
       logical first  
       save first  
       data first/.true./  
       DATA iadvtr/0/  
   
       if(first) then  
   
         CALL initfluxsto(  
      .  time_step,istdyn* time_step,istdyn* time_step,  
      . nqmx, fluxid,fluxvid,fluxdid)  
           
         ndex(1) = 0  
         call histwrite(fluxid, 'phis', 1, phis)  
         call histwrite(fluxid, 'aire', 1, aire)  
           
         ndex(1) = 0  
         nscal = 1  
         tst(1) = time_step  
         call histwrite(fluxdid, 'dtvr', 1, tst)  
         ist(1)=istdyn  
         call histwrite(fluxdid, 'istdyn', 1, ist)  
         istp(1)= istphy  
         call histwrite(fluxdid, 'istphy', 1, istp)  
           
         first = .false.  
   
       endif  
   
   
       IF(iadvtr.EQ.0) THEN  
          CALL initial0(ijp1llm,phic)  
          CALL initial0(ijp1llm,tetac)  
          CALL initial0(ijp1llm,pbaruc)  
          CALL initial0(ijmllm,pbarvc)  
       ENDIF  
   
 c   accumulation des flux de masse horizontaux  
       DO l=1,llm  
          DO ij = 1,ip1jmp1  
             pbaruc(ij,l) = pbaruc(ij,l) + pbaru(ij,l)  
             tetac(ij,l) = tetac(ij,l) + teta(ij,l)  
             phic(ij,l) = phic(ij,l) + phi(ij,l)  
          ENDDO  
          DO ij = 1,ip1jm  
             pbarvc(ij,l) = pbarvc(ij,l) + pbarv(ij,l)  
          ENDDO  
       ENDDO  
   
 c   selection de la masse instantannee des mailles avant le transport.  
       IF(iadvtr.EQ.0) THEN  
          CALL SCOPY(ip1jmp1*llm,masse,1,massem,1)  
       ENDIF  
   
       iadvtr   = iadvtr+1  
   
   
 c   Test pour savoir si on advecte a ce pas de temps  
       IF ( iadvtr.EQ.istdyn ) THEN  
 c    normalisation  
       DO l=1,llm  
          DO ij = 1,ip1jmp1  
             pbaruc(ij,l) = pbaruc(ij,l)/float(istdyn)  
             tetac(ij,l) = tetac(ij,l)/float(istdyn)  
             phic(ij,l) = phic(ij,l)/float(istdyn)  
          ENDDO  
          DO ij = 1,ip1jm  
             pbarvc(ij,l) = pbarvc(ij,l)/float(istdyn)  
          ENDDO  
       ENDDO  
   
 c   traitement des flux de masse avant advection.  
 c     1. calcul de w  
 c     2. groupement des mailles pres du pole.  
   
         CALL groupe( massem, pbaruc,pbarvc, pbarug,pbarvg,wg )  
   
         do l=1,llm  
            do j=1,jjm  
               do i=1,iip1  
                  pbarvst(i,j,l)=pbarvg(i,j,l)  
               enddo  
            enddo  
            do i=1,iip1  
               pbarvst(i,jjp1,l)=0.  
            enddo  
         enddo  
   
          iadvtr=0  
         Print*,'ITAU auqel on stoke les fluxmasses',itau  
           
         call histwrite(fluxid, 'masse', itau, massem)  
           
         call histwrite(fluxid, 'pbaru', itau, pbarug)  
           
         call histwrite(fluxvid, 'pbarv', itau, pbarvg)  
           
         call histwrite(fluxid, 'w' ,itau, wg)  
           
         call histwrite(fluxid, 'teta' ,itau, tetac)  
           
         call histwrite(fluxid, 'phi' ,itau, phic)  
           
 C  
4    
5        ENDIF ! if iadvtr.EQ.istdyn    USE histwrite_m, ONLY : histwrite
6      USE dimens_m, ONLY : jjm, llm, nqmx
7      USE paramet_m, ONLY : iip1, ijmllm, ijp1llm, ip1jm, ip1jmp1, jjp1
8      USE comgeom, ONLY : aire
9      USE tracstoke, ONLY : istdyn, istphy
10    
11      IMPLICIT NONE
12    
13      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
14      REAL masse(ip1jmp1, llm), teta(ip1jmp1, llm), phi(ip1jmp1, llm)
15      REAL phis(ip1jmp1)
16      REAL, intent(in):: time_step
17      INTEGER, INTENT (IN) :: itau
18    
19      ! Variables local to the procedure:
20    
21      REAL, SAVE:: pbaruc(ip1jmp1, llm), pbarvc(ip1jm, llm)
22      REAL, SAVE:: massem(ip1jmp1, llm)
23      real, SAVE:: tetac(ip1jmp1, llm), phic(ip1jmp1, llm)
24    
25      REAL pbarug(ip1jmp1, llm), pbarvg(iip1, jjm, llm), wg(ip1jmp1, llm)
26      INTEGER:: iadvtr = 0
27      REAL tst(1), ist(1), istp(1)
28      INTEGER ij, l
29      INTEGER, save:: fluxid, fluxvid
30      integer fluxdid
31      LOGICAL:: first = .TRUE.
32    
33      !-------------------------------------------------------------
34    
35      IF (first) THEN
36         CALL initfluxsto(time_step, istdyn*time_step, istdyn*time_step, nqmx, &
37              fluxid, fluxvid, fluxdid)
38         CALL histwrite(fluxid, 'phis', 1, phis)
39         CALL histwrite(fluxid, 'aire', 1, aire)
40         tst(1) = time_step
41         CALL histwrite(fluxdid, 'dtvr', 1, tst)
42         ist(1) = istdyn
43         CALL histwrite(fluxdid, 'istdyn', 1, ist)
44         istp(1) = istphy
45         CALL histwrite(fluxdid, 'istphy', 1, istp)
46    
47         first = .FALSE.
48      END IF
49    
50      IF (itau == 0) THEN
51         CALL initial0(ijp1llm, phic)
52         CALL initial0(ijp1llm, tetac)
53         CALL initial0(ijp1llm, pbaruc)
54         CALL initial0(ijmllm, pbarvc)
55      END IF
56    
57      !   accumulation des flux de masse horizontaux
58      DO l = 1, llm
59         DO ij = 1, ip1jmp1
60            pbaruc(ij, l) = pbaruc(ij, l) + pbaru(ij, l)
61            tetac(ij, l) = tetac(ij, l) + teta(ij, l)
62            phic(ij, l) = phic(ij, l) + phi(ij, l)
63         END DO
64         DO ij = 1, ip1jm
65            pbarvc(ij, l) = pbarvc(ij, l) + pbarv(ij, l)
66         END DO
67      END DO
68    
69      !   selection de la masse instantannee des mailles avant le transport.
70      IF (itau == 0) THEN
71         CALL scopy(ip1jmp1*llm, masse, 1, massem, 1)
72      END IF
73    
74      iadvtr = iadvtr + 1
75    
76      !   Test pour savoir si on advecte a ce pas de temps
77      IF (iadvtr == istdyn) THEN
78         !    normalisation
79         DO l = 1, llm
80            DO ij = 1, ip1jmp1
81               pbaruc(ij, l) = pbaruc(ij, l)/float(istdyn)
82               tetac(ij, l) = tetac(ij, l)/float(istdyn)
83               phic(ij, l) = phic(ij, l)/float(istdyn)
84            END DO
85            DO ij = 1, ip1jm
86               pbarvc(ij, l) = pbarvc(ij, l)/float(istdyn)
87            END DO
88         END DO
89    
90         !   traitement des flux de masse avant advection.
91         !     1. calcul de w
92         !     2. groupement des mailles pres du pole.
93    
94         CALL groupe(massem, pbaruc, pbarvc, pbarug, pbarvg, wg)
95         iadvtr = 0
96         PRINT *, 'ITAU auqel on stoke les fluxmasses', itau
97    
98         CALL histwrite(fluxid, 'masse', itau, massem)
99         CALL histwrite(fluxid, 'pbaru', itau, pbarug)
100         CALL histwrite(fluxvid, 'pbarv', itau, pbarvg)
101         CALL histwrite(fluxid, 'w', itau, wg)
102         CALL histwrite(fluxid, 'teta', itau, tetac)
103         CALL histwrite(fluxid, 'phi', itau, phic)
104      END IF                                
105    
106        RETURN  END SUBROUTINE fluxstokenc
       END  

Legend:
Removed from v.27  
changed lines
  Added in v.31

  ViewVC Help
Powered by ViewVC 1.1.21