Changeset 1871


Ignore:
Timestamp:
Dec 20, 2017, 12:23:42 PM (7 years ago)
Author:
jvatant
Message:

Making chemistry handling more flexible - Step 1
+ Enable upper_chemistry_dimension in the startfi files
+ Added a comchem_h for all the chemistry related stuff
+ start2archive adapted to these modifs : next step newstart !
--JVO

Location:
trunk/LMDZ.TITAN
Files:
1 added
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/README

    r1795 r1871  
    13421342For now on you can do microphysics but no clouds yet ( you can but you shouldn't !)
    13431343Big modifs of the tracer gestion/init in the physiq with a new query by names (see tracer_h )
     1344
     1345== 20/12/2017 - ... : r1871- ... == JVO
     1346Management of the chemistry within startfi. Open the way to :
     1347 1) run with chemistry in another resolution than 32x48 !
     1348 2) parallelize chemistry
     1349 3) Dynamico
     1350... at least it's impossible without these modifs !
     1351Main idea : The upper chemistry (up to 1300km) fields are now stored in startfi
     1352rather than read in the middle of calchim as before from compo files
     1353+ An "upper_chemistry_layers" dimension is now handled in startfi files
     1354+ This dimension is also stored in tabfi
     1355+ Added a comchem_h.F90 module for all the stuff related to chemistry
     1356+ ...
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/newstart.F

    r1850 r1871  
    66c   Auteur:   Christophe Hourdin/Francois Forget/Yann Wanherdrick
    77c   ------
    8 c             Derniere modif : 12/03
    9 c
    10 c
    11 c   Objet:  Create or modify the initial state for the LMD Mars GCM
     8c
     9c   Objet:  Create or modify the initial state for the LMD Titan GCM
    1210c   -----           (fichiers NetCDF start et startfi)
    1311c
     
    568566      write(*,*) 'flat : no topography ("aquaplanet")'
    569567      write(*,*) 'set_ps_to_preff : used if changing preff with topo'
    570       write(*,*) 'nuketharsis : no Tharsis bulge'
    571568      write(*,*) 'bilball : uniform albedo and thermal inertia'
    572       write(*,*) 'coldspole : cold subsurface and high albedo at S.pole'
    573569      write(*,*) 'qname : change tracer name'
    574570      write(*,*) 't=profile  : read temperature profile in profile.in'
     
    582578!      write(*,*) 'ini_q-iceH2O : tracers initialisation for chemistry on
    583579!     $ly '
    584       write(*,*) 'noglacier : Remove tropical H2O ice if |lat|<45'
    585       write(*,*) 'watercapn : H20 ice on permanent N polar cap '
    586       write(*,*) 'watercaps : H20 ice on permanent S polar cap '
    587       write(*,*) 'noacglac  : H2O ice across Noachis Terra'
    588       write(*,*) 'oborealis : H2O ice across Vastitas Borealis'
    589       write(*,*) 'iceball   : Thick ice layer all over surface'
    590       write(*,*) 'supercontinent: Create a continent of given Ab and TI'
    591       write(*,*) 'wetstart  : start with a wet atmosphere'
    592580      write(*,*) 'isotherm  : Isothermal Temperatures, wind set to zero'
    593581      write(*,*) 'radequi   : Earth-like radiative equilibrium temperature
    594582     $ profile (lat-alt) and winds set to zero'
    595       write(*,*) 'coldstart : Start X K above the CO2 frost point and
    596      $set wind to zero (assumes 100% CO2)'
    597       write(*,*) 'co2ice=0 : remove CO2 polar cap'
    598583      write(*,*) 'ptot : change total pressure'
    599584      write(*,*) 'emis : change surface emissivity'
     
    664649          enddo
    665650
    666 c       'nuketharsis : no tharsis bulge for Early Mars'
    667 c       ---------------------------------------------
    668         else if (trim(modif) .eq. 'nuketharsis') then
    669 
    670            DO j=1,jjp1       
    671               DO i=1,iim
    672                  ig=1+(j-2)*iim +i
    673                  if(j.eq.1) ig=1
    674                  if(j.eq.jjp1) ig=ngridmx
    675 
    676                  fact1=(((rlonv(i)*180./pi)+100)**2 +
    677      &                (rlatu(j)*180./pi)**2)/65**2
    678                  fact2=exp( -fact1**2.5 )
    679 
    680                  phis(i,j) = phis(i,j) - (phis(i,j)+4000.*g)*fact2
    681 
    682 !                 if(phis(i,j).gt.2500.*g)then
    683 !                    if(rlatu(j)*180./pi.gt.-80.)then ! avoid chopping south polar cap
    684 !                       phis(i,j)=2500.*g
    685 !                    endif
    686 !                 endif
    687 
    688               ENDDO
    689            ENDDO
    690           CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,phis,phisfi)
    691 
    692651
    693652c       bilball : uniform albedo, thermal inertia
     
    717676          CALL gr_dyn_fi(nsoilmx,iip1,jjp1,ngridmx,ith,ithfi)
    718677          CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,alb,albfi)
    719 
    720 c       coldspole : sous-sol de la calotte sud toujours froid
    721 c       -----------------------------------------------------
    722         else if (trim(modif) .eq. 'coldspole') then
    723           write(*,*)'new value for the subsurface temperature',
    724      &   ' beneath the permanent southern polar cap ? (eg: 141 K)'
    725  103      read(*,*,iostat=ierr) tsud
    726           if(ierr.ne.0) goto 103
    727           write(*,*)
    728           write(*,*) ' new value of the subsurface temperature:',tsud
    729 c         nouvelle temperature sous la calotte permanente
    730           do l=2,nsoilmx
    731                tsoil(ngridmx,l) =  tsud
    732           end do
    733 
    734 
    735           write(*,*)'new value for the albedo',
    736      &   'of the permanent southern polar cap ? (eg: 0.75)'
    737  104      read(*,*,iostat=ierr) albsud
    738           if(ierr.ne.0) goto 104
    739           write(*,*)
    740 
    741 c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    742 c         Option 1:  only the albedo of the pole is modified :   
    743           albfi(ngridmx)=albsud
    744           write(*,*) 'ig=',ngridmx,'   albedo perennial cap ',
    745      &    albfi(ngridmx)
    746 
    747 c         ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    748 c          Option 2 A haute resolution : coordonnee de la vrai calotte ~   
    749 c           DO j=1,jjp1
    750 c             DO i=1,iip1
    751 c                ig=1+(j-2)*iim +i
    752 c                if(j.eq.1) ig=1
    753 c                if(j.eq.jjp1) ig=ngridmx
    754 c                if ((rlatu(j)*180./pi.lt.-84.).and.
    755 c     &            (rlatu(j)*180./pi.gt.-91.).and.
    756 c     &            (rlonv(i)*180./pi.gt.-91.).and.
    757 c     &            (rlonv(i)*180./pi.lt.0.))         then
    758 cc    albedo de la calotte permanente fixe a albsud
    759 c                   alb(i,j)=albsud
    760 c                   write(*,*) 'lat=',rlatu(j)*180./pi,
    761 c     &                      ' lon=',rlonv(i)*180./pi
    762 cc     fin de la condition sur les limites de la calotte permanente
    763 c                end if
    764 c             ENDDO
    765 c          ENDDO
    766 c      ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    767 
    768 c         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,alb,albfi)
    769 
    770678
    771679c       ptot : Modification of the total pressure: ice + current atmosphere
     
    1024932             
    1025933
    1026 c      wetstart : wet atmosphere with a north to south gradient
    1027 c      --------------------------------------------------------
    1028        else if (trim(modif) .eq. 'wetstart') then
    1029         ! check that there is indeed a water vapor tracer
    1030 
    1031           write(*,*) "No water vapour tracer! Can't use this option"
    1032           stop
    1033 
    1034 c      noglacier : remove tropical water ice (to initialize high res sim)
    1035 c      --------------------------------------------------
    1036         else if (trim(modif) .eq. 'noglacier') then
    1037        
    1038              write(*,*) "No water ice tracer! Can't use this option"
    1039              stop
    1040 
    1041 
    1042 
    1043 c      watercapn : H20 ice on permanent northern cap
    1044 c      --------------------------------------------------
    1045         else if (trim(modif) .eq. 'watercapn') then
    1046        
    1047              write(*,*) "No water ice tracer! Can't use this option"
    1048              stop
    1049 
    1050 c      watercaps : H20 ice on permanent southern cap
    1051 c      -------------------------------------------------
    1052         else if (trim(modif) .eq. 'watercaps') then
    1053 
    1054               write(*,*) "No water ice tracer! Can't use this option"
    1055               stop
    1056 
    1057 c       noacglac : H2O ice across highest terrain
    1058 c       --------------------------------------------
    1059         else if (trim(modif) .eq. 'noacglac') then
    1060 
    1061              write(*,*) "No water ice tracer! Can't use this option"
    1062              stop
    1063 
    1064 c       oborealis : H2O oceans across Vastitas Borealis
    1065 c       -----------------------------------------------
    1066         else if (trim(modif) .eq. 'oborealis') then
    1067 
    1068              write(*,*) "No water ice tracer! Can't use this option"
    1069              stop
    1070              
    1071 c       iborealis : H2O ice in Northern plains
    1072 c       --------------------------------------
    1073         else if (trim(modif) .eq. 'iborealis') then
    1074 
    1075              write(*,*) "No water ice tracer! Can't use this option"
    1076              stop
    1077 
    1078 c       oceanball : H2O liquid everywhere
    1079 c       ----------------------------
    1080         else if (trim(modif) .eq. 'oceanball') then
    1081 
    1082              write(*,*) "No water ice tracer! Can't use this option"
    1083              stop
    1084 
    1085 c       iceball : H2O ice everywhere
    1086 c       ----------------------------
    1087         else if (trim(modif) .eq. 'iceball') then
    1088 
    1089              write(*,*) "No water ice tracer! Can't use this option"
    1090              stop
    1091 
    1092 c       supercontinent : H2O ice everywhere
    1093 c       ----------------------------
    1094         else if (trim(modif) .eq. 'supercontinent') then
    1095  
    1096              write(*,*) "No water ice tracer! Can't use this option"
    1097              stop
    1098 
    1099934c       isotherm : Isothermal temperatures and no winds
    1100935c       -----------------------------------------------
     
    1153988          q2(1:ngridmx,1:llm+1)=0
    1154989
    1155 c       coldstart : T set 1K above CO2 frost point and no winds
    1156 c       ------------------------------------------------
    1157         else if (trim(modif) .eq. 'coldstart') then
    1158 
    1159           write(*,*)'set temperature of the atmosphere,'
    1160      &,'surface and subsurface how many degrees above CO2 frost point?'
    1161  204      read(*,*,iostat=ierr) Tabove
    1162           if(ierr.ne.0) goto 204
    1163 
    1164             DO j=1,jjp1
    1165              DO i=1,iim
    1166                 ig=1+(j-2)*iim +i
    1167                 if(j.eq.1) ig=1
    1168                 if(j.eq.jjp1) ig=ngridmx
    1169             tsurf(ig) = (-3167.8)/(log(.01*ps(i,j))-23.23)+Tabove
    1170              END DO
    1171             END DO
    1172           do l=1,nsoilmx
    1173             do ig=1, ngridmx
    1174               tsoil(ig,l) = tsurf(ig)
    1175             end do
    1176           end do
    1177           DO j=1,jjp1
    1178            DO i=1,iim
    1179             Do l=1,llm
    1180                pp = aps(l) +bps(l)*ps(i,j)
    1181                Tset(i,j,l)=(-3167.8)/(log(.01*pp)-23.23)+Tabove
    1182             end do
    1183            end do
    1184           end do
    1185 
    1186           flagtset=.true.
    1187           ucov(1:iip1,1:jjp1,1:llm)=0
    1188           vcov(1:iip1,1:jjm,1:llm)=0
    1189           q2(1:ngridmx,1:llm+1)=0
    1190 
    1191 
    1192 c       co2ice=0 : remove CO2 polar ice caps'
    1193 c       ------------------------------------------------
    1194         else if (trim(modif) .eq. 'co2ice=0') then
    1195             write(*,*) "Can't remove CO2 ice!! (no co2_ice tracer)"
    1196        
    1197        
    1198990!       therm_ini_s: (re)-set soil thermal inertia to reference surface values
    1199991!       ----------------------------------------------------------------------
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/start2archive.F

    r1815 r1871  
    2121      use infotrac, only: infotrac_init, nqtot, tname
    2222      USE comsoil_h
    23      
     23      USE comchem_h
     24
    2425!      USE comgeomfi_h, ONLY: lati, long, area
    2526!      use control_mod
     
    8182      INTEGER*4 day_ini_fi
    8283
    83 !     added by JVO for methane surface tank
    84       REAL tankCH4(ngridmx)
     84c     Added by JVO for Titan specifities
     85      REAL tankCH4(ngridmx) ! Depth of surface methane tank
     86     
     87      ! + Titan upper atm. chemistry 44 fields in comchem_h
    8588
    8689c Variable naturelle / grille scalaire
     
    9497      REAL emisS(ip1jmp1)
    9598
    96 !     added by JVO for methane surface tank
    97       REAL tankCH4S(ip1jmp1)
    98 
     99c     Added by JVO for Titan specifities
     100      REAL tankCH4S(ip1jmp1)  ! Depth of surface methane tank
     101
     102      ! + Titan upper atm. chemistry 44 fields in comchem_h
     103 
    99104c Variables intermediaires : vent naturel, mais pas coord scalaire
    100105c----------------------------------------------------------------
     
    105110      LOGICAL startdrs
    106111      INTEGER Lmodif
     112
     113      LOGICAL nokim
    107114
    108115      REAL ptotal
     
    192199       CALL abort
    193200      ENDIF
    194       ierr = NF_CLOSE(nid1)
    195201     
    196202      ! allocate arrays of nsoilmx size
     
    198204      allocate(tsoilS(ip1jmp1,nsoilmx))
    199205      allocate(ithS(ip1jmp1,nsoilmx))
     206
     207! Get value of the "upper_chemistry_layers" dimension from physics start file
     208
     209      ierr = NF_INQ_DIMID(nid1,"upper_chemistry_layers",varid)
     210      IF (ierr .NE. NF_NOERR) THEN
     211       PRINT*, "start2archive: No upper_chemistry_layers dimension!!"
     212       CALL abort
     213      ENDIF
     214      ierr = NF_INQ_DIMLEN(nid1,varid,nlaykim_up)
     215      IF (ierr .NE. NF_NOERR) THEN
     216       PRINT*, "start2archive: Failed reading
     217     . upper_chemistry_layers value!!"
     218       CALL abort
     219      ENDIF
     220     
     221      ! Allocate arrays of nlaykim_up size, only if they're present
     222      ! The test is on HCN but could be on any as we assume we can't do incomplete chemistry
     223
     224      ierr = NF_INQ_VARID(nid1,'HCN_up',varid)
     225      IF (ierr .NE. NF_NOERR) THEN
     226        PRINT*, "start2archive: Missing field(s) for upper chemistry ...
     227     . I presume they're all absent !"
     228        nokim=.TRUE.
     229      ELSE
     230        PRINT*,"start2archive: I found a field for upper chemistry ...
     231     . I presume they're all here as you can't do uncomplete chemistry!"
     232        ! Allocates upper chemistry fields in comchem_h on physical and scalar grid
     233        CALL allokim_start2archive(ngridmx,ip1jmp1)
     234      ENDIF
     235
     236      ierr = NF_CLOSE(nid1)
    200237
    201238c-----------------------------------------------------------------------
     
    316353c qsurf --> qsurfS
    317354c tankCH4 --> tankCH4S
     355c + all 44 chemistry fields
    318356c
    319357c-----------------------------------------------------------------------
     
    327365      call gr_fi_dyn(nqtot,ngridmx,iip1,jjp1,qsurf,qsurfS)
    328366      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tankCH4,tankCH4S)
     367
     368      IF (nokim .eqv. .FALSE.) THEN ! NB : fields are in comchem_h
     369         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,H,H_S)
     370         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,H2,H2_S)
     371         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH,CH_S)
     372         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH2s,CH2s_S)
     373         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH2,CH2_S)
     374         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH3,CH3_S)
     375         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH4,CH4_S)
     376         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C2,C2_S)
     377         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C2H,C2H_S)
     378         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C2H2,C2H2_S)
     379         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C2H3,C2H3_S)
     380         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C2H4,C2H4_S)
     381         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C2H5,C2H5_S)
     382         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C2H6,C2H6_S)
     383         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C3H3,C3H3_S)
     384         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C3H5,C3H5_S)
     385         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C3H6,C3H6_S)
     386         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C3H7,C3H7_S)
     387         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H,C4H_S)
     388         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H3,C4H3_S)
     389         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H4,C4H4_S)
     390         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H2s,C4H2s_S)
     391         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH2CCH2,CH2CCH2_S)
     392         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH3CCH,CH3CCH_S)
     393         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C3H8,C3H8_S)
     394         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H2,C4H2_S)
     395         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H6,C4H6_S)
     396         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H10,C4H10_S)
     397         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,AC6H6,AC6H6_S)
     398         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C3H2,C3H2_S)
     399         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4H5,C4H5_S)
     400         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,AC6H5,AC6H5_S)
     401         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,N2,N2_S)
     402         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,N4S,N4S_S)
     403         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CN,CN_S)
     404         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,HCN,HCN_S)
     405         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,H2CN,H2CN_S)
     406         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CHCN,CHCN_S)
     407         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH2CN,CH2CN_S)
     408         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,CH3CN,CH3CN_S)
     409         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C3N,C3N_S)
     410         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,HC3N,HC3N_S)
     411         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,NCCN,NCCN_S)
     412         call gr_fi_dyn(nlaykim_up,ngridmx,iip1,jjp1,C4N2,C4N2_S)
     413      ENDIF
    329414
    330415c=======================================================================
     
    400485
    401486c-----------------------------------------------------------------------
    402 c Ecriture des champs  (emis,ps,Tsurf,T,u,v,q2,q,qsurf)
     487c Ecriture des champs  (emis,ps,Tsurf,T,u,v,q2,q,qsurf,tankCH4)
    403488c-----------------------------------------------------------------------
    404489c ATTENTION: q2 a une couche de plus!!!!
     
    471556     &         'Depth of surface methane tank','m',2,tankCH4S)
    472557
     558c-----------------------------------------------------------------
     559c Ecriture des champs upper_chemistry
     560c-----------------------------------------------------------------
     561
     562      IF (nokim .eqv. .FALSE.) THEN
     563         call write_archive(nid,ntime,'H_up',
     564     .              'H in upper atmosphere','kg/kg',4,H_S)
     565         call write_archive(nid,ntime,'H2_up',
     566     .              'H2 in upper atmosphere','kg/kg',4,H2_S)
     567         call write_archive(nid,ntime,'CH_up',
     568     .              'CH in upper atmosphere','kg/kg',4,CH_S)
     569         call write_archive(nid,ntime,'CH2s_up',
     570     .              'CH2s in upper atmosphere','kg/kg',4,CH2s_S)
     571         call write_archive(nid,ntime,'CH2_up',
     572     .              'CH2 in upper atmosphere','kg/kg',4,CH2_S)
     573         call write_archive(nid,ntime,'CH3_up',
     574     .              'CH3 in upper atmosphere','kg/kg',4,CH3_S)
     575         call write_archive(nid,ntime,'CH4_up',
     576     .              'CH4 in upper atmosphere','kg/kg',4,CH4_S)
     577         call write_archive(nid,ntime,'C2_up',
     578     .              'C2 in upper atmosphere','kg/kg',4,C2_S)
     579         call write_archive(nid,ntime,'C2H_up',
     580     .              'C2H in upper atmosphere','kg/kg',4,C2H_S)
     581         call write_archive(nid,ntime,'C2H2_up',
     582     .              'C2H2 in upper atmosphere','kg/kg',4,C2H2_S)
     583         call write_archive(nid,ntime,'C2H3_up',
     584     .              'C2H3 in upper atmosphere','kg/kg',4,C2H3_S)
     585         call write_archive(nid,ntime,'C2H4_up',
     586     .              'C2H4 in upper atmosphere','kg/kg',4,C2H4_S)
     587         call write_archive(nid,ntime,'C2H5_up',
     588     .              'C2H5 in upper atmosphere','kg/kg',4,C2H5_S)
     589         call write_archive(nid,ntime,'C2H6_up',
     590     .              'C2H6 in upper atmosphere','kg/kg',4,C2H6_S)
     591         call write_archive(nid,ntime,'C3H3_up',
     592     .              'C3H3 in upper atmosphere','kg/kg',4,C3H3_S)
     593         call write_archive(nid,ntime,'C3H5_up',
     594     .              'C3H5 in upper atmosphere','kg/kg',4,C3H5_S)
     595         call write_archive(nid,ntime,'C3H6_up',
     596     .              'C3H6 in upper atmosphere','kg/kg',4,C3H6_S)
     597         call write_archive(nid,ntime,'C3H7_up',
     598     .              'C3H7 in upper atmosphere','kg/kg',4,C3H7_S)
     599         call write_archive(nid,ntime,'C4H_up',
     600     .              'C4H in upper atmosphere','kg/kg',4,C4H_S)
     601         call write_archive(nid,ntime,'C4H3_up',
     602     .              'C4H3 in upper atmosphere','kg/kg',4,C4H3_S)
     603         call write_archive(nid,ntime,'C4H4_up',
     604     .              'C4H4 in upper atmosphere','kg/kg',4,C4H4_S)
     605         call write_archive(nid,ntime,'C4H2s_up',
     606     .              'C4H2s in upper atmosphere','kg/kg',4,C4H2s_S)
     607         call write_archive(nid,ntime,'CH2CCH2_up',
     608     .              'CH2CCH2 in upper atmosphere','kg/kg',4,CH2CCH2_S)
     609         call write_archive(nid,ntime,'CH3CCH_up',
     610     .              'CH3CCH in upper atmosphere','kg/kg',4,CH3CCH_S)
     611         call write_archive(nid,ntime,'C3H8_up',
     612     .              'C3H8 in upper atmosphere','kg/kg',4,C3H8_S)
     613         call write_archive(nid,ntime,'C4H2_up',
     614     .              'C4H2 in upper atmosphere','kg/kg',4,C4H2_S)
     615         call write_archive(nid,ntime,'C4H6_up',
     616     .              'C4H6 in upper atmosphere','kg/kg',4,C4H6_S)
     617         call write_archive(nid,ntime,'C4H10_up',
     618     .              'C4H10 in upper atmosphere','kg/kg',4,C4H10_S)
     619         call write_archive(nid,ntime,'AC6H6_up',
     620     .              'AC6H6 in upper atmosphere','kg/kg',4,AC6H6_S)
     621         call write_archive(nid,ntime,'C3H2_up',
     622     .              'C3H2 in upper atmosphere','kg/kg',4,C3H2_S)
     623         call write_archive(nid,ntime,'C4H5_up',
     624     .              'C4H5 in upper atmosphere','kg/kg',4,C4H5_S)
     625         call write_archive(nid,ntime,'AC6H5_up',
     626     .              'AC6H5 in upper atmosphere','kg/kg',4,AC6H5_S)
     627         call write_archive(nid,ntime,'N2_up',
     628     .              'N2 in upper atmosphere','kg/kg',4,N2_S)
     629         call write_archive(nid,ntime,'N4S_up',
     630     .              'N4S in upper atmosphere','kg/kg',4,N4S_S)
     631         call write_archive(nid,ntime,'CN_up',
     632     .              'CN in upper atmosphere','kg/kg',4,CN_S)
     633         call write_archive(nid,ntime,'HCN_up',
     634     .              'HCN in upper atmosphere','kg/kg',4,HCN_S)
     635         call write_archive(nid,ntime,'H2CN_up',
     636     .              'H2CN in upper atmosphere','kg/kg',4,H2CN_S)
     637         call write_archive(nid,ntime,'CHCN_up',
     638     .              'CHCN in upper atmosphere','kg/kg',4,CHCN_S)
     639         call write_archive(nid,ntime,'CH2CN_up',
     640     .              'CH2CN in upper atmosphere','kg/kg',4,CH2CN_S)
     641         call write_archive(nid,ntime,'CH3CN_up',
     642     .              'CH3CN in upper atmosphere','kg/kg',4,CH3CN_S)
     643         call write_archive(nid,ntime,'C3N_up',
     644     .              'C3N in upper atmosphere','kg/kg',4,C3N_S)
     645         call write_archive(nid,ntime,'HC3N_up',
     646     .              'HC3N in upper atmosphere','kg/kg',4,HC3N_S)
     647         call write_archive(nid,ntime,'NCCN_up',
     648     .              'NCCN in upper atmosphere','kg/kg',4,NCCN_S)
     649         call write_archive(nid,ntime,'C4N2_up',
     650     .              'C4N2 in upper atmosphere','kg/kg',4,C4N2_S)
     651      ENDIF
     652
    473653c Fin
    474654c-----------------------------------------------------------------------
  • trunk/LMDZ.TITAN/libf/dynphy_lonlat/phytitan/write_archive.F

    r1647 r1871  
    3333
    3434      use comsoil_h, only: nsoilmx
     35      use comchem_h, only: nlaykim_up
    3536
    3637      implicit none
     
    160161#endif
    161162
    162 ! For a 3D ocean temperature Variable
    163 !-------------------------------
    164 
    165         else if (dim.eq.-2) then
     163
     164! For a 3D upper chemistry Variable
     165!----------------------------------
     166
     167        else if (dim.eq.4) then
    166168        ! get variables' ID, if it exists
    167169        ierr=NF_INQ_VARID(nid,nom,varid)
     
    171173          ierr=NF_INQ_DIMID(nid,"longitude",id(1))
    172174          ierr=NF_INQ_DIMID(nid,"latitude",id(2))
    173           ierr=NF_INQ_DIMID(nid,"ocean_layers",id(3))
     175          ierr=NF_INQ_DIMID(nid,"upper_chemistry_layers",id(3))
    174176          if (ierr.ne.NF_NOERR) then
    175            write(*,*)"write_archive: dimension <ocean_layers>",
    176      &               " is missing !!!"
     177           write(*,*)"write_archive: dimension
     178     &                <upper_chemistry_layers> is missing !!!"
    177179           call abort
    178180          endif
     
    194196        edges(1)=iip1
    195197        edges(2)=jjp1
    196         edges(3)=1 ! JVO2017 : was noceanmx before -> set to 1
     198        edges(3)=nlaykim_up
    197199        edges(4)=1
    198200#ifdef NC_DOUBLE
     
    201203           ierr= NF_PUT_VARA_REAL(nid,varid,corner,edges,px)
    202204#endif
    203 
    204205
    205206
  • trunk/LMDZ.TITAN/libf/phytitan/iostart.F90

    r1815 r1871  
    1515    INTEGER,SAVE :: idim6 ! "nlayer" dimension
    1616    INTEGER,SAVE :: idim7 ! "Time" dimension
     17    INTEGER,SAVE :: idim8 ! "upper_chemistry_layers" dimension
    1718    INTEGER,SAVE :: timeindex ! current time index (for time-dependent fields)
    18 !$OMP THREADPRIVATE(idim1,idim2,idim3,idim4,idim5,idim6,idim7,timeindex)
     19!$OMP THREADPRIVATE(idim1,idim2,idim3,idim4,idim5,idim6,idim7,idim8,idim9,timeindex)
    1920    INTEGER,PARAMETER :: length=100 ! size of tab_cntrl array
    2021   
     
    468469  USE tracer_h, only: nqtot_p
    469470  USE comsoil_h, only: nsoilmx
     471  USE comchem_h, only: nlaykim_up
    470472
    471473  IMPLICIT NONE
     
    556558      ENDIF
    557559
     560      ierr=NF90_DEF_DIM(nid_restart,"upper_chemistry_layers",nlaykim_up,idim8)
     561      IF (ierr/=NF90_NOERR) THEN
     562        write(*,*)'open_restartphy: problem defining upper_chemistry_layers dimension '
     563        write(*,*)trim(nf90_strerror(ierr))
     564        CALL ABORT
     565      ENDIF
     566     
    558567      ierr=NF90_ENDDEF(nid_restart)
    559568      IF (ierr/=NF90_NOERR) THEN
     
    634643  USE dimphy
    635644  USE comsoil_h, only: nsoilmx
     645  USE comchem_h, only: nlaykim_up
    636646  USE mod_grid_phy_lmdz
    637647  USE mod_phys_lmdz_para
     
    807817            ierr=NF90_DEF_VAR(nid_restart,field_name,NF90_FLOAT,&
    808818                              (/idim2,idim3,idim7/),nvarid)
     819#endif
     820           if (ierr.ne.NF90_NOERR) then
     821              write(*,*)"put_field_rgen error: failed to define "//trim(field_name)
     822              write(*,*)trim(nf90_strerror(ierr))
     823            endif
     824            IF (LEN_TRIM(title) > 0) ierr=NF90_PUT_ATT(nid_restart,nvarid,"title",title)
     825            ierr=NF90_ENDDEF(nid_restart)
     826          endif
     827          ! Write the variable
     828          ierr=NF90_PUT_VAR(nid_restart,nvarid,field_glo,&
     829                            start=(/1,1,timeindex/))
     830
     831        endif ! of if (.not.present(time))
     832
     833      ELSE IF (field_size==nlaykim_up) THEN
     834        ! input is a 2D "upper chemistry" array
     835        if (.not.present(time)) then ! for a time-independent field
     836          ierr = NF90_REDEF(nid_restart)
     837#ifdef NC_DOUBLE
     838          ierr=NF90_DEF_VAR(nid_restart,field_name,NF90_DOUBLE,&
     839                            (/idim2,idim8/),nvarid)
     840#else
     841          ierr=NF90_DEF_VAR(nid_restart,field_name,NF90_FLOAT,&
     842                            (/idim2,idim8/),nvarid)
     843#endif
     844          if (ierr.ne.NF90_NOERR) then
     845            write(*,*)"put_field_rgen error: failed to define "//trim(field_name)
     846            write(*,*)trim(nf90_strerror(ierr))
     847          endif
     848          IF (LEN_TRIM(title) > 0) ierr=NF90_PUT_ATT(nid_restart,nvarid,"title",title)
     849          ierr = NF90_ENDDEF(nid_restart)
     850          ierr = NF90_PUT_VAR(nid_restart,nvarid,field_glo)
     851        else
     852          ! check if the variable has already been defined:
     853          ierr=NF90_INQ_VARID(nid_restart,field_name,nvarid)
     854          if (ierr/=NF90_NOERR) then ! variable not found, define it
     855            ierr=NF90_REDEF(nid_restart)
     856#ifdef NC_DOUBLE
     857            ierr=NF90_DEF_VAR(nid_restart,field_name,NF90_DOUBLE,&
     858                              (/idim2,idim8,idim7/),nvarid)
     859#else
     860            ierr=NF90_DEF_VAR(nid_restart,field_name,NF90_FLOAT,&
     861                              (/idim2,idim8,idim7/),nvarid)
    809862#endif
    810863           if (ierr.ne.NF90_NOERR) then
  • trunk/LMDZ.TITAN/libf/phytitan/tabfi_mod.F90

    r1670 r1871  
    5555                           emissiv
    5656      use comsoil_h, only: volcapa
     57      use comchem_h, only: nlaykim_up
    5758      use iostart, only: get_var
    5859      use mod_phys_lmdz_para, only: is_parallel
     
    149150        dtemisice(:)=0 !time scale for snow metamorphism
    150151        volcapa=1000000 ! volumetric heat capacity of subsurface
    151 
     152! chemistry
     153        nlaykim_up=70 ! size of vertical grid for upper chemistry
     154       
    152155      ELSE
    153156!-----------------------------------------------------------------------
     
    204207! soil properties
    205208      volcapa = tab_cntrl(tab0+35) ! volumetric heat capacity
     209! chemistry
     210      nlaykim_up = nint(tab_cntrl(tab0+40)) ! size of vertical grid for upper chemistry
    206211!-----------------------------------------------------------------------
    207212!       Save some constants for later use (as routine arguments)
     
    256261
    257262      write(*,5) '(35)        volcapa',tab_cntrl(tab0+35),volcapa
     263
     264      write(*,5) '(40)     nlaykim_up',tab_cntrl(tab0+40),float(nlaykim_up)
    258265
    259266      write(*,*)
     
    564571 
    565572      write(*,5) '(35)        volcapa',tab_cntrl(tab0+35),volcapa
     573     
     574      write(*,5) '(40)     nlaykim_up',tab_cntrl(tab0+40),float(nlaykim_up)
    566575
    567576      write(*,*) 
Note: See TracChangeset for help on using the changeset viewer.