Changeset 2824


Ignore:
Timestamp:
Nov 18, 2022, 4:46:50 PM (2 years ago)
Author:
emillour
Message:

Mars GCM:
A first step at cleaning/improving the xvik program: updated comments
and changed output yearly dates range to include sol=669.0 (i.e. last
time step of the year).
EM

Location:
trunk/LMDZ.MARS
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2823 r2824  
    37873787Remove the "tracer" (logical) flag as we now always run with at least
    37883788one tracer.
     3789
     3790== 18/11/2022 == EM
     3791A first step at cleaning/improving the xvik program: updated comments
     3792and changed output yearly dates range to include sol=669.0 (i.e. last
     3793time step of the year).
  • trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/xvik.F

    r2325 r2824  
    33      USE filtreg_mod, ONLY: inifilr
    44      USE comconst_mod, ONLY: dtvr,g,r,pi
    5      
     5      USE comvert_mod, ONLY: pa,preff
    66     
    77      IMPLICIT NONE
     
    3838      CHARACTER*100  varname
    3939      INTEGER ierr,nid,nvarid,dimid
    40       LOGICAL nc
    4140      INTEGER start_ps(3),start_temp(4),start_co2ice(3)
    4241      INTEGER count_ps(3),count_temp(4),count_co2ice(3)
     
    103102c   initialisations:
    104103c-----------------------------------------------------------------------
     104      pi=4.*atan(1.)
     105      pa=20
     106      preff=610.
    105107
    106108      chr2="0"
     109      iyear=0
    107110      unanj=669.
    108       print*,'WARNING!!!',unanj,'Jours/an'
    109       nc=.true.
     111      print*,'WARNING!!! Assuming',unanj,'sols/year'
     112     
     113c-----------------------------------------------------------------------
     114c   Viking Lander coordinates:
     115c   --------------------------------------------------------------------
     116
     117      lonvik(1) = lonvik1
     118      latvik(1) = latvik1
     119      lonvik(2) = lonvik2
     120      latvik(2) = latvik2
    110121     
    111122      phivik(1) = phivik1
    112123      phivik(2) = phivik2
    113124     
    114       print *, 'COORDVIKIIIN', latvik, lonvik
    115       print*, 'LES PHIVIK', phivik
    116      
    117      
    118 
    119 
    120 
    121       WRITE(*,*) 'Chemin des fichiers histoires'
     125      WRITE(*,*) 'Viking coordinates:'
     126      WRITE(*,*) 'latvik:',latvik,' lonvik:',lonvik
     127      WRITE(*,*) 'Phivik:', phivik
     128     
     129      ! convert coordinates to radians
     130      lonvik(1) = lonvik1 * pi/180.
     131      latvik(1) = latvik1 * pi/180.
     132      lonvik(2) = lonvik2 * pi/180.
     133      latvik(2) = latvik2 * pi/180.
     134     
     135
     136      WRITE(*,*) 'Path to the diagfi files directory'
    122137      READ (*,'(a)')  pathchmp
    123       WRITE(*,*) 'Chemin des fichiers sorties'
     138      WRITE(*,*) 'Path to the dir for outputs'
    124139      READ (*,'(a)')  pathsor
    125140     
    126       WRITE(*,*) 'Fichiers de sortie en sol (1)
    127      &,en ls (2) ,les deux (3)'
     141      WRITE(*,*) 'Output file time axis in sol (1) '//
     142     &'in ls (2) ,or both (3)'
    128143      READ (*,*)  Time_unit
    129144     
     
    135150
    136151c-----------------------------------------------------------------------
    137 c   ouverture des fichiers xgraph:
     152c   output files:
    138153c-----------------------------------------------------------------------
    139154      ifile(1)=12
     
    143158     
    144159     
    145       print*,'Entrer un fichier NC (sans le .nc)'
     160      print*,'diagfi file name (without trailing .nc)'
    146161      READ(5,'(a)',err=9999) nomfich
    147162     
    148163
    149164c%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    150 c   grande boucle sur les fichiers histoire:
     165c   loop on the diagfi files:
    151166c%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    152167
     
    164179      PRINT*,'timestep ',dtvr
    165180
    166       IF(nc) THEN
    167181      ierr= NF_OPEN(file(1:len_trim(file))//'.nc',NF_NOWRITE,nid)       
    168       ELSE
    169          PRINT*,'Ouverture binaire ',file
    170          OPEN(unitlec,file=file,status='old',form='unformatted',
    171      .   iostat=ierr)
    172       ENDIF
    173 
    174 c----------------------------------------------------------------------
    175 c   initialisation de la physique:
     182
     183c----------------------------------------------------------------------
     184c   initialise physics:
    176185c----------------------------------------------------------------------
    177186
     
    211220       
    212221       
    213 c-----------------------------------------------------------------------
    214 c   coordonnees des point Viking:
    215 c   --------------------------------------------------------------------
    216 
    217       lonvik(1) = lonvik1 * pi/180.
    218       latvik(1) = latvik1 * pi/180.
    219       lonvik(2) = lonvik2 * pi/180.
    220       latvik(2) = latvik2 * pi/180.
    221      
    222222                   
    223223c----------------------------------------------------------------------   
     
    255255
    256256c----------------------------------------------------------------------
    257 c   altitude reelle et modele aux points Viking
     257c   true and model altitude at Viking locations
    258258c----------------------------------------------------------------------
    259259
     
    269269         ENDDO
    270270      ENDDO
    271       PRINT*,'relief aux points Viking pour les sorties:',phivik
     271      PRINT*,'phivik at Viking locations for outputs:',phivik
    272272           
    273273
    274274c----------------------------------------------------------------------
    275 c   lectures des etats:
     275c   read variables:
    276276c   -------------------------------------------------------------------
    277277
     
    294294       
    295295c----------------------------------------------------------------------       
    296 c   lecture drs des champs:
    297 c----------------------------------------------------------------------
    298 
    299 
    300 ccccccccc  LECTURE Ps ccccccccccccccccccccccccccc
     296c   read fields:
     297c----------------------------------------------------------------------
     298
     299
     300ccccccccc  Load Ps ccccccccccccccccccccccccccc
    301301
    302302
     
    314314          PRINT*,'ps',ps(iip1/2,jjp1/2)
    315315
    316 ccccccccc  LECTURE Temperature ccccccccccccccccccccccccccc
     316ccccccccc  Load Temperature ccccccccccccccccccccccccccc
    317317
    318318
     
    353353
    354354
    355 ccccccccc  LECTURE co2ice ccccccccccccccccccccccccccc
     355ccccccccc  Load co2ice ccccccccccccccccccccccccccc
    356356
    357357
     
    370370
    371371c----------------------------------------------------------------------
    372 c Gestion du temps
     372c Handle calendar
    373373c ---------------------------------------------------------------------
    374374
     
    376376          PRINT*,'day ',day
    377377          sol=day+day0
    378           iyear=sol/unanj
    379           WRITE (*,*) 'iyear',iyear
    380           sol=sol-iyear*unanj
    381 
    382 c----------------------------------------------------------------------
    383 c Ouverture / fermeture des fichiers
     378          do while (sol.gt.unanj)
     379            sol=sol-unanj
     380          enddo
     381          WRITE (*,*) 'sol: ',sol,' iyear:',iyear
     382
     383c----------------------------------------------------------------------
     384c Open /close files
    384385c ---------------------------------------------------------------------
    385386
    386387          IF (iyear.NE.kyear) THEN
    387388             WRITE(chr2(1:1),'(i1)') iyear+1
    388              WRITE (*,*) 'iyear bis',iyear
    389              WRITE (*,*) 'chr2'
    390              WRITE (*,*)  chr2
     389             WRITE (*,*) 'iyear bis:',iyear
     390             WRITE (*,*) 'chr2:',trim(chr2)
    391391             IF(iyear.GE.9) WRITE(chr2,'(i2)') iyear+1
    392392             kyear=iyear
     
    417417         
    418418c----------------------------------------------------------------------
    419 c Calcul de la moyenne de pression planetaire
     419c Compute average planetary pressure
    420420c ---------------------------------------------------------------------
    421421
     
    442442
    443443
    444 c --------------Ecriture fichier sortie xprestot-----------------------
     444c --------------Write output file xprestot-----------------------
    445445c  Sol ou ls ou les deux
    446446c  Ps_moy_planetaire (Pa)
     
    465465
    466466c----------------------------------------------------------------------
    467 c boucle sur les sites vikings:
    468 c----------------------------------------------------------------------
    469 
    470 c----------------------------------------------------------------------
    471 c interpolation de la temperature dans la 7eme couche, de la pression
    472 c de surface et des vents aux points viking.
     467c Loop on Viking sites:
     468c----------------------------------------------------------------------
     469
     470c----------------------------------------------------------------------
     471c interapolate using temperature in the 7th layer, of surface pressure
    473472c----------------------------------------------------------------------
    474473
     
    491490                   zt=zt+zw(ii,jj,iv)*t7(i,j)
    492491                   zp1=zp1+zw(ii,jj,iv)*log(ps(i,j)) ! interpolate in log(P)
    493                    WRITE (*,*) 'ps autour iv',ps(i,j),iv
     492                   WRITE (*,*) 'ps around iv',ps(i,j),iv
    494493
    495494                ENDDO
     
    502501             
    503502c----------------------------------------------------------------------
    504 pression au sol extrapolee a partir de la temp. 7eme couche
     503surface pressure extrapolated using temp. from 7th atmospheric layer
    505504c----------------------------------------------------------------------
    506505           
     
    514513          WRITE (*,*) 'iv,pstot,zp2, zp1, phivik(iv),phisim(iv),gh'
    515514          WRITE (*,*) iv,pstot*airtot1,zp2,zp1,phivik(iv),phisim(iv),gh
     515          WRITE(*,*) "------"
    516516             
    517517
    518 c ------Ecriture 2 fichiers (1 pour Vl1, 1 pour VL2) sortie xpsol ------
    519 c  Sol ou ls ou les deux
    520 c  Ps site VLi (i=1,2) a  l'altitude GCM (Pa)
    521 c  Ps site VLi (i=1,2) a  l'altitude exacte  (interpolee) (Pa)
     518c ------Write 2 files (1 for Vl1, 1 for VL2) xpsol ------
     519c  Sol or ls or both
     520c  Ps site VLi (i=1,2) at GCM altitude (Pa)
     521c  Ps site VLi (i=1,2) at true (interpolated) altitude (Pa)
    522522             
    523523             IF(Time_unit == 1) THEN
     
    537537
    538538c======================================================================
    539 c   Fin de la boucle sur les etats du fichier histoire:
     539c   End of loop of variables in the diagfi file
    540540c======================================================================
    541541
     542       if (sol.ge.unanj-1.e-5) then
     543         ! end of year reached (with some roundoff margin)
     544         ! increment iyear
     545         iyear=iyear+1
     546       endif
     547
    542548      ENDDO
    543549
    544550      ierr= NF_CLOSE(nid)
    545551
    546       PRINT*,'Fin du fichier',nomfich
    547       print*,'Entrer un nouveau fichier NC
    548      &(sans le .nc) ou return pour finir'
     552      PRINT*,'End of file',nomfich
     553      print*,'Entrer new file name (without trailing .nc)',
     554     &" or return to end"
    549555      READ(5,'(a)',err=9999) nomfich
    550556
    551557
    552558c%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    553 c   Fin de la boucle sur les fichiers histoire:
     559c   End of loop on the diagfi files
    554560c%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
    555561
    556562      ENDDO
    557563
    558       PRINT*,'relief du point V1',.001*phis(ivik(1),jvik(1))/g
    559       PRINT*,'relief du point V2',.001*phis(ivik(2),jvik(2))/g
     564      PRINT*,'altitude of VL1',.001*phis(ivik(1),jvik(1))/g
     565      PRINT*,'altitude of VL2',.001*phis(ivik(2),jvik(2))/g
    560566      DO iv=1,2
    561567         PRINT*,'Viking',iv,'   i=',ivik(iv),'j  =',jvik(iv)
     
    570576         print*,'zw'
    571577         write(6,'(2(2f10.4/))') ((zw(ii,jj,iv),ii=0,1),jj=0,1)
    572          print*,'altitude interpolee (km) ',phisim(iv)/1000./g
     578         print*,'interpolated altitude (km) ',phisim(iv)/1000./g
    573579      ENDDO
    574580      PRINT*,'R=',r
    575  9999  PRINT*,'Fin '
     581 9999  PRINT*,'End '
    576582
    5775837777  FORMAT ('latitude/longitude',4f7.1)
     
    659665!==============================================================================
    660666
    661 count_years=0 ! initialize
     667      count_years=0 ! initialize
    662668      zz=sol  ! use "zz" to store (and work on) the value of sol
    663669      do while (zz.ge.year_day)
Note: See TracChangeset for help on using the changeset viewer.