Ignore:
Timestamp:
Dec 20, 2013, 4:04:56 PM (11 years ago)
Author:
emillour
Message:

Mars GCM:
Series of changes to enable running in parallel (using LMDZ.COMMON dynamics);
Current LMDZ.MARS can still notheless be compiled and run in serial mode
"as previously".
Summary of main changes:

  • Main programs (newstart, start2archive, xvik) that used to be in dyn3d have been moved to phymars.
  • dyn3d/control.h is now module control_mod.F90
  • rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallel case)
  • created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the min and max of a field over the whole planet.

EM

File:
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/phymars/newstart.F

    r1087 r1130  
    1717! to use  'getin'
    1818      use ioipsl_getincom, only: getin
    19       use infotrac, only: iniadvtrac, nqtot, tnom
    20       use tracer_mod, only: noms, igcm_h2o_vap, igcm_h2o_ice
     19      use infotrac, only: iniadvtrac, nqtot, tname
     20      use tracer_mod, only: noms, igcm_dust_number, igcm_dust_mass,
     21     &                      igcm_ccn_number, igcm_ccn_mass,
     22     &                      igcm_h2o_vap, igcm_h2o_ice
    2123      use surfdat_h, only: phisfi, z0, zmea, zstd, zsig, zgam, zthe,
    2224     &                     albedodat, z0_default
    2325      use comsoil_h, only: inertiedat, layer, mlayer, nsoilmx
     26      use control_mod, only: day_step, iphysiq, anneeref
     27      use phyredem, only: physdem0, physdem1
     28      use iostart, only: open_startphy
     29      use comgeomphy, only: initcomgeomphy
    2430      implicit none
    2531
     
    3642#include "comvert.h"
    3743#include "comgeom2.h"
    38 #include "control.h"
     44!#include "control.h"
    3945#include "logic.h"
    4046#include "description.h"
    4147#include "ener.h"
    4248#include "temps.h"
    43 #include "lmdstd.h"
     49!#include "lmdstd.h"
    4450#include "comdissnew.h"
    4551#include "clesph0.h"
     
    142148c variables diverses
    143149c-------------------
    144       real choix_1
     150      real choix_1 ! ==0 : read start_archive file ; ==1: read start files
    145151      character*80      fichnom
    146152      integer Lmodif,iq
     
    183189      preff  = 610.    ! for Mars, instead of 101325. (Earth)
    184190      pa= 20           ! for Mars, instead of 500 (Earth)
     191
     192! initialize "serial/parallel" related stuff
     193      CALL init_phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
     194      call initcomgeomphy
    185195
    186196! Load tracer number and names:
     
    316326c-----------------------------------------------------------------------
    317327      if (choix_1.eq.0) then
     328         ! tabfi requires that input file be first opened by open_startphy(fichnom)
     329         fichnom = 'start_archive.nc'
     330         call open_startphy(fichnom)
    318331         call tabfi (nid,Lmodif,tab0,day_ini,lllm,p_rad,
    319332     .            p_omeg,p_g,p_mugaz,p_daysec,time)
    320333      else if (choix_1.eq.1) then
     334         fichnom = 'startfi.nc'
     335         call open_startphy(fichnom)
    321336         call tabfi (nid_fi,Lmodif,tab0,day_ini,lllm,p_rad,
    322337     .            p_omeg,p_g,p_mugaz,p_daysec,time)
     
    461476        txt=" "
    462477        write(txt,'(a1,i2.2)') 'q',iq
    463         if (txt.eq.tnom(iq)) then
     478        if (txt.eq.tname(iq)) then
    464479          count=count+1
    465480        endif
     
    471486      if (count.eq.nqtot) then
    472487        write(*,*) 'Newstart: updating tracer names'
    473         ! copy noms(:) to tnom(:) to have matching tracer names in physics
     488        ! copy noms(:) to tname(:) to have matching tracer names in physics
    474489        ! and dynamics
    475         tnom(1:nqtot)=noms(1:nqtot)
     490        tname(1:nqtot)=noms(1:nqtot)
    476491      endif
    477492
     
    497512     $ tracer'
    498513      write(*,*) 'q=profile    : specify a profile for a tracer'
     514      write(*,*) 'freedust     : rescale dust to a true value'
    499515      write(*,*) 'ini_q        : tracers initialization for chemistry
    500516     $ and water vapour'
     
    723739          write(*,*) 'Which tracer name do you want to change ?'
    724740          do iq=1,nqtot
    725             write(*,'(i3,a3,a20)')iq,' : ',trim(tnom(iq))
     741            write(*,'(i3,a3,a20)')iq,' : ',trim(tname(iq))
    726742          enddo
    727743          write(*,'(a35,i3)')
     
    730746          read(*,*) iq
    731747          if ((iq.ge.1).and.(iq.le.nqtot)) then
    732             write(*,*)'Change tracer name ',trim(tnom(iq)),' to ?'
     748            write(*,*)'Change tracer name ',trim(tname(iq)),' to ?'
    733749            read(*,*) txt
    734             tnom(iq)=txt
     750            tname(iq)=txt
    735751            write(*,*)'Do you want to change another tracer name (y/n)?'
    736752            read(*,'(a)') yes
     
    768784             write(*,*) 'Which tracer do you want to modify ?'
    769785             do iq=1,nqtot
    770                write(*,*)iq,' : ',trim(tnom(iq))
     786               write(*,*)iq,' : ',trim(tname(iq))
    771787             enddo
    772788             write(*,*) '(choose between 1 and ',nqtot,')'
     
    777793               cycle
    778794             endif
    779              write(*,*)'mixing ratio of tracer ',trim(tnom(iq)),
     795             write(*,*)'mixing ratio of tracer ',trim(tname(iq)),
    780796     &                 ' ? (kg/kg)'
    781797             read(*,*) val
     
    787803               ENDDO
    788804             ENDDO
    789              write(*,*) 'SURFACE value of tracer ',trim(tnom(iq)),
     805             write(*,*) 'SURFACE value of tracer ',trim(tname(iq)),
    790806     &                   ' ? (kg/m2)'
    791807             read(*,*) val
     
    804820             write(*,*) 'Which tracer do you want to set?'
    805821             do iq=1,nqtot
    806                write(*,*)iq,' : ',trim(tnom(iq))
     822               write(*,*)iq,' : ',trim(tname(iq))
    807823             enddo
    808824             write(*,*) '(choose between 1 and ',nqtot,')'
     
    814830             endif
    815831             ! look for input file 'profile_tracer'
    816              txt="profile_"//trim(tnom(iq))
     832             txt="profile_"//trim(tname(iq))
    817833             open(41,file=trim(txt),status='old',form='formatted',
    818834     &            iostat=ierr)
     
    831847                   q(:,:,l,iq)=profile(l+1)
    832848                 enddo
    833                  write(*,*)'OK, tracer ',trim(tnom(iq)),' initialized ',
    834      &                     'using values from file ',trim(txt)
     849                 write(*,*)'OK, tracer ',trim(tname(iq)),
     850     &               ' initialized ','using values from file ',trim(txt)
    835851               else
    836852                 write(*,*)'problem reading file ',trim(txt),' !'
    837                  write(*,*)'No modifications to tracer ',trim(tnom(iq))
     853                 write(*,*)'No modifications to tracer ',trim(tname(iq))
    838854               endif
    839855             else
    840856               write(*,*)'Could not find file ',trim(txt),' !'
    841                write(*,*)'No modifications to tracer ',trim(tnom(iq))
     857               write(*,*)'No modifications to tracer ',trim(tname(iq))
    842858             endif
    843859             
     860c       q=profile : initialize tracer with a given profile
     861c       --------------------------------------------------
     862        else if (trim(modif) .eq. 'freedust') then
     863          do l=1,llm
     864            do j=1,jjp1
     865              do i=1,iip1
     866                if (igcm_dust_number .ne. 0)
     867     &          q(i,j,l,igcm_dust_number)=
     868     &                q(i,j,l,igcm_dust_number) * 1e-3 ! grosso modo
     869                if (igcm_dust_mass .ne. 0)
     870     &          q(i,j,l,igcm_dust_mass)=
     871     &                q(i,j,l,igcm_dust_mass)   * 1e-3 ! grosso modo
     872                if (igcm_ccn_number .ne. 0)
     873     &          q(i,j,l,igcm_ccn_number)=
     874     &                q(i,j,l,igcm_ccn_number) * 1e-3 ! grosso modo
     875                if (igcm_ccn_mass .ne. 0)
     876     &          q(i,j,l,igcm_ccn_mass)=
     877     &                q(i,j,l,igcm_ccn_mass)   * 1e-3 ! grosso modo
     878              end do
     879            end do
     880          end do
     881
     882         ! We want to have the very same value at lon -180 and lon 180
     883          do l = 1,llm
     884             do j = 1,jjp1
     885                do iq = 1,nqtot
     886                   q(iip1,j,l,iq) = q(1,j,l,iq)
     887                end do
     888             end do
     889          end do
    844890
    845891c       ini_q : Initialize tracers for chemistry
Note: See TracChangeset for help on using the changeset viewer.