source: LMDZ6/branches/Amaury_dev/libf/dyn3d/fluxstokenc.F90 @ 5116

Last change on this file since 5116 was 5116, checked in by abarral, 8 weeks ago

rename modules properly lmdz_*
move ismin, ismax, minmax into new lmdz_libmath.f90
(lint) uppercase fortran keywords

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