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

Diff of /trunk/Sources/dyn3d/fluxstokenc.f

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

trunk/libf/dyn3d/fluxstokenc.f90 revision 68 by guez, Wed Nov 14 16:59:30 2012 UTC trunk/Sources/dyn3d/fluxstokenc.f revision 208 by guez, Wed Dec 7 16:44:53 2016 UTC
# Line 1  Line 1 
1  SUBROUTINE fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, time_step, itau)  module fluxstokenc_m
2    
3    ! Author: F. Hourdin    IMPLICIT NONE
4    
5    USE histwrite_m, ONLY : histwrite  contains
   USE dimens_m, ONLY : jjm, llm, nqmx  
   USE paramet_m, ONLY : iip1, ijmllm, ijp1llm, ip1jm, ip1jmp1, jjp1  
   USE comgeom, ONLY : aire  
   USE tracstoke, ONLY : istdyn, istphy  
6    
7    IMPLICIT NONE    SUBROUTINE fluxstokenc(pbaru, pbarv, masse, teta, phi, phis, time_step, itau)
8    
9        ! Author: F. Hourdin
10    
11        USE comgeom, ONLY: aire
12        USE dimens_m, ONLY: jjm, llm
13        use groupe_m, only: groupe
14        USE histwrite_m, ONLY: histwrite
15        use initfluxsto_m, only: initfluxsto
16        USE paramet_m, ONLY: iip1, ijmllm, ijp1llm, ip1jm, ip1jmp1
17        USE tracstoke, ONLY: istdyn, istphy
18    
19        REAL, intent(in):: pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
20        REAL, intent(in):: masse(ip1jmp1, llm)
21        real, intent(in):: phi(ip1jmp1, llm)
22        real, intent(in):: teta(ip1jmp1, llm)
23        REAL, intent(in):: phis(ip1jmp1)
24        REAL, intent(in):: time_step
25        INTEGER, INTENT (IN):: itau
26    
27        ! Local:
28    
29        REAL, SAVE:: pbaruc(ip1jmp1, llm), pbarvc(ip1jm, llm)
30        REAL, SAVE:: massem(ip1jmp1, llm)
31        real, SAVE:: tetac(ip1jmp1, llm), phic(ip1jmp1, llm)
32    
33        REAL pbarug(ip1jmp1, llm), pbarvg(iip1, jjm, llm), wg(ip1jmp1, llm)
34        REAL tst(1), ist(1), istp(1)
35        INTEGER ij, l
36        INTEGER, save:: fluxid, fluxvid
37        integer fluxdid
38    
39        !-------------------------------------------------------------
40    
41        IF (itau == 0) THEN
42           CALL initfluxsto(time_step, istdyn*time_step, istdyn*time_step, &
43                fluxid, fluxvid, fluxdid)
44           CALL histwrite(fluxid, 'phis', 1, phis)
45           CALL histwrite(fluxid, 'aire', 1, aire)
46           tst(1) = time_step
47           CALL histwrite(fluxdid, 'dtvr', 1, tst)
48           ist(1) = istdyn
49           CALL histwrite(fluxdid, 'istdyn', 1, ist)
50           istp(1) = istphy
51           CALL histwrite(fluxdid, 'istphy', 1, istp)
52    
53           CALL initial0(ijp1llm, phic)
54           CALL initial0(ijp1llm, tetac)
55           CALL initial0(ijp1llm, pbaruc)
56           CALL initial0(ijmllm, pbarvc)
57        END IF
58    
59        ! Accumulation des flux de masse horizontaux
60        DO l = 1, llm
61           DO ij = 1, ip1jmp1
62              pbaruc(ij, l) = pbaruc(ij, l) + pbaru(ij, l)
63              tetac(ij, l) = tetac(ij, l) + teta(ij, l)
64              phic(ij, l) = phic(ij, l) + phi(ij, l)
65           END DO
66           DO ij = 1, ip1jm
67              pbarvc(ij, l) = pbarvc(ij, l) + pbarv(ij, l)
68           END DO
69        END DO
70    
71        ! S\'election de la masse instantan\'ee des mailles avant le transport.
72        IF (itau == 0) massem = masse
73    
74        IF (mod(itau + 1, istdyn) == 0) THEN
75           ! On advecte \`a ce pas de temps
76           ! normalisation
77           DO l = 1, llm
78              DO ij = 1, ip1jmp1
79                 pbaruc(ij, l) = pbaruc(ij, l)/real(istdyn)
80                 tetac(ij, l) = tetac(ij, l)/real(istdyn)
81                 phic(ij, l) = phic(ij, l)/real(istdyn)
82              END DO
83              DO ij = 1, ip1jm
84                 pbarvc(ij, l) = pbarvc(ij, l)/real(istdyn)
85              END DO
86           END DO
87    
88           ! Traitement des flux de masse avant advection.
89           ! 1. Calcul de w
90           ! 2. Groupement des mailles pr\`es du p\^ole.
91           CALL groupe(pbaruc, pbarvc, pbarug, pbarvg, wg)
92    
93           CALL histwrite(fluxid, 'masse', itau, massem)
94           CALL histwrite(fluxid, 'pbaru', itau, pbarug)
95           CALL histwrite(fluxvid, 'pbarv', itau, pbarvg)
96           CALL histwrite(fluxid, 'w', itau, wg)
97           CALL histwrite(fluxid, 'teta', itau, tetac)
98           CALL histwrite(fluxid, 'phi', itau, phic)
99        END IF
100    
101    REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)    END SUBROUTINE fluxstokenc
   REAL masse(ip1jmp1, llm)  
   real, intent(in):: phi(ip1jmp1, llm)  
   real, intent(in):: teta(ip1jmp1, llm)  
   REAL phis(ip1jmp1)  
   REAL, intent(in):: time_step  
   INTEGER, INTENT (IN) :: itau  
   
   ! Variables local to the procedure:  
   
   REAL, SAVE:: pbaruc(ip1jmp1, llm), pbarvc(ip1jm, llm)  
   REAL, SAVE:: massem(ip1jmp1, llm)  
   real, SAVE:: tetac(ip1jmp1, llm), phic(ip1jmp1, llm)  
   
   REAL pbarug(ip1jmp1, llm), pbarvg(iip1, jjm, llm), wg(ip1jmp1, llm)  
   REAL tst(1), ist(1), istp(1)  
   INTEGER ij, l  
   INTEGER, save:: fluxid, fluxvid  
   integer fluxdid  
   
   !-------------------------------------------------------------  
   
   IF (itau == 0) THEN  
      CALL initfluxsto(time_step, istdyn*time_step, istdyn*time_step, nqmx, &  
           fluxid, fluxvid, fluxdid)  
      CALL histwrite(fluxid, 'phis', 1, phis)  
      CALL histwrite(fluxid, 'aire', 1, aire)  
      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)  
   
      CALL initial0(ijp1llm, phic)  
      CALL initial0(ijp1llm, tetac)  
      CALL initial0(ijp1llm, pbaruc)  
      CALL initial0(ijmllm, pbarvc)  
   END IF  
   
   !   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)  
      END DO  
      DO ij = 1, ip1jm  
         pbarvc(ij, l) = pbarvc(ij, l) + pbarv(ij, l)  
      END DO  
   END DO  
   
   !   selection de la masse instantannee des mailles avant le transport.  
   IF (itau == 0) THEN  
      CALL scopy(ip1jmp1*llm, masse, 1, massem, 1)  
   END IF  
   
   IF (mod(itau + 1, istdyn) == 0) THEN  
      ! on advecte a ce pas de temps  
      !    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)  
         END DO  
         DO ij = 1, ip1jm  
            pbarvc(ij, l) = pbarvc(ij, l)/float(istdyn)  
         END DO  
      END DO  
   
      !   traitement des flux de masse avant advection.  
      !     1. calcul de w  
      !     2. groupement des mailles pres du pole.  
   
      CALL groupe(massem, pbaruc, pbarvc, pbarug, pbarvg, wg)  
   
      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)  
   END IF                                  
102    
103  END SUBROUTINE fluxstokenc  end module fluxstokenc_m

Legend:
Removed from v.68  
changed lines
  Added in v.208

  ViewVC Help
Powered by ViewVC 1.1.21