[1279] | 1 | ! $Id: writehist.f90 5118 2024-07-24 14:39:59Z abarral $ |
---|
[5099] | 2 | |
---|
[5114] | 3 | SUBROUTINE writehist(time, vcov, ucov, teta, phi, q, masse, ps, phis) |
---|
[524] | 4 | |
---|
[5105] | 5 | USE ioipsl |
---|
| 6 | USE infotrac, ONLY: nqtot |
---|
[5114] | 7 | USE com_io_dyn_mod, ONLY: histid, histvid, histuid |
---|
[5105] | 8 | USE temps_mod, ONLY: itau_dyn |
---|
[5114] | 9 | USE lmdz_description, ONLY: descript |
---|
[5118] | 10 | USE lmdz_iniprint, ONLY: lunout, prt_level |
---|
[524] | 11 | |
---|
[5113] | 12 | IMPLICIT NONE |
---|
[524] | 13 | |
---|
[5105] | 14 | ! |
---|
| 15 | ! Ecriture du fichier histoire au format IOIPSL |
---|
| 16 | ! |
---|
| 17 | ! Appels succesifs des routines: histwrite |
---|
| 18 | ! |
---|
| 19 | ! Entree: |
---|
| 20 | ! time: temps de l'ecriture |
---|
| 21 | ! vcov: vents v covariants |
---|
| 22 | ! ucov: vents u covariants |
---|
| 23 | ! teta: temperature potentielle |
---|
| 24 | ! phi : geopotentiel instantane |
---|
| 25 | ! q : traceurs |
---|
| 26 | ! masse: masse |
---|
| 27 | ! ps :pression au sol |
---|
| 28 | ! phis : geopotentiel au sol |
---|
| 29 | ! |
---|
| 30 | ! |
---|
| 31 | ! L. Fairhead, LMD, 03/99 |
---|
| 32 | ! |
---|
| 33 | ! ===================================================================== |
---|
| 34 | ! |
---|
| 35 | ! Declarations |
---|
| 36 | include "dimensions.h" |
---|
| 37 | include "paramet.h" |
---|
| 38 | include "comgeom.h" |
---|
[524] | 39 | |
---|
[5105] | 40 | ! |
---|
| 41 | ! Arguments |
---|
| 42 | ! |
---|
[524] | 43 | |
---|
[5114] | 44 | REAL :: vcov(ip1jm, llm), ucov(ip1jmp1, llm) |
---|
| 45 | REAL :: teta(ip1jmp1, llm), phi(ip1jmp1, llm) |
---|
| 46 | REAL :: ps(ip1jmp1), masse(ip1jmp1, llm) |
---|
[5105] | 47 | REAL :: phis(ip1jmp1) |
---|
[5114] | 48 | REAL :: q(ip1jmp1, llm, nqtot) |
---|
[5116] | 49 | INTEGER :: time |
---|
[524] | 50 | |
---|
[1403] | 51 | |
---|
[5105] | 52 | ! This routine needs IOIPSL to work |
---|
| 53 | ! Variables locales |
---|
| 54 | ! |
---|
[5116] | 55 | INTEGER :: iq, ii, ll |
---|
| 56 | INTEGER :: ndexu(ip1jmp1 * llm), ndexv(ip1jm * llm), ndex2d(ip1jmp1) |
---|
[5117] | 57 | LOGICAL :: ok_sync |
---|
[5116] | 58 | INTEGER :: itau_w |
---|
[5114] | 59 | REAL :: vnat(ip1jm, llm), unat(ip1jmp1, llm) |
---|
[524] | 60 | |
---|
[5105] | 61 | ! |
---|
| 62 | ! Initialisations |
---|
| 63 | ! |
---|
| 64 | ndexu = 0 |
---|
| 65 | ndexv = 0 |
---|
| 66 | ndex2d = 0 |
---|
[5114] | 67 | ok_sync = .TRUE. |
---|
[5105] | 68 | itau_w = itau_dyn + time |
---|
| 69 | ! Passage aux composantes naturelles du vent |
---|
| 70 | CALL covnat(llm, ucov, vcov, unat, vnat) |
---|
| 71 | ! |
---|
| 72 | ! Appels a histwrite pour l'ecriture des variables a sauvegarder |
---|
| 73 | ! |
---|
| 74 | ! Vents U |
---|
| 75 | ! |
---|
| 76 | CALL histwrite(histuid, 'u', itau_w, unat, & |
---|
[5114] | 77 | iip1 * jjp1 * llm, ndexu) |
---|
[5105] | 78 | ! |
---|
| 79 | ! Vents V |
---|
| 80 | ! |
---|
| 81 | CALL histwrite(histvid, 'v', itau_w, vnat, & |
---|
[5114] | 82 | iip1 * jjm * llm, ndexv) |
---|
[5105] | 83 | |
---|
| 84 | ! |
---|
| 85 | ! Temperature potentielle |
---|
| 86 | ! |
---|
| 87 | CALL histwrite(histid, 'teta', itau_w, teta, & |
---|
[5114] | 88 | iip1 * jjp1 * llm, ndexu) |
---|
[5105] | 89 | ! |
---|
| 90 | ! Geopotentiel |
---|
| 91 | ! |
---|
| 92 | CALL histwrite(histid, 'phi', itau_w, phi, & |
---|
[5114] | 93 | iip1 * jjp1 * llm, ndexu) |
---|
[5105] | 94 | ! |
---|
| 95 | ! Traceurs |
---|
| 96 | ! |
---|
| 97 | ! DO iq=1,nqtot |
---|
| 98 | ! CALL histwrite(histid, tracers(iq)%longName, itau_w, |
---|
| 99 | ! . q(:,:,iq), iip1*jjp1*llm, ndexu) |
---|
| 100 | ! enddo |
---|
| 101 | !C |
---|
| 102 | ! Masse |
---|
| 103 | ! |
---|
[5114] | 104 | CALL histwrite(histid, 'masse', itau_w, masse, iip1 * jjp1 * llm, ndexu) |
---|
[5105] | 105 | ! |
---|
| 106 | ! Pression au sol |
---|
| 107 | ! |
---|
[5114] | 108 | CALL histwrite(histid, 'ps', itau_w, ps, iip1 * jjp1, ndex2d) |
---|
[5105] | 109 | ! |
---|
| 110 | ! Geopotentiel au sol |
---|
| 111 | ! |
---|
| 112 | ! CALL histwrite(histid, 'phis', itau_w, phis, iip1*jjp1, ndex2d) |
---|
| 113 | ! |
---|
| 114 | ! Fin |
---|
| 115 | ! |
---|
[5117] | 116 | IF (ok_sync) THEN |
---|
[5105] | 117 | CALL histsync(histid) |
---|
| 118 | CALL histsync(histvid) |
---|
| 119 | CALL histsync(histuid) |
---|
[5117] | 120 | ENDIF |
---|
[5116] | 121 | RETURN |
---|
| 122 | END SUBROUTINE writehist |
---|