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

Last change on this file since 5220 was 5159, checked in by abarral, 3 months ago

Put dimensions.h and paramet.h into modules

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