Changeset 1233


Ignore:
Timestamp:
May 1, 2014, 12:06:13 AM (11 years ago)
Author:
aslmd
Message:

LMDZ.MARS. Filling geom arrays is now out of phys_var_state_init. Done through a merged function ini_fillgeom within the comgeomfi_h module. Cosmetic changes. New interface with the mesoscale model: lesser amount of dirty MESOSCALE includes.

Location:
trunk/LMDZ.MARS
Files:
4 deleted
10 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r1232 r1233  
    20512051(saved arrays) which have been moved to modules.
    20522052
     2053== 01/05/2014 == AS
     2054- Filling geom arrays is now out of phys_var_state_init. Done
     2055  through a merged function ini_fillgeom within the comgeomfi_h module.
     2056- Cosmetic changes
     2057- New interface with the mesoscale model: lesser amount of dirty MESOSCALE includes
  • trunk/LMDZ.MARS/libf/phymars/comgeomfi_h.F90

    r1224 r1233  
    2424         allocate(long(ngrid))
    2525         allocate(area(ngrid))
    26 
    27          end subroutine ini_comgeomfi_h
    28 
    29          subroutine ini_sincosgeom(ngrid)
    30 
    31          implicit none
    32          integer,intent(in) :: ngrid ! number of atmospheric columns
    33          integer :: ig
    34 
    35          if (.not.allocated(lati)) then
    36            PRINT*,"lati not allocated. did you run ini_comgeomfi_h?"
    37            STOP
    38          endif
    39 
    4026         allocate(sinlat(ngrid))
    4127         allocate(coslat(ngrid))
    4228         allocate(sinlon(ngrid))
    4329         allocate(coslon(ngrid))
     30
     31         end subroutine ini_comgeomfi_h
     32
     33         subroutine ini_fillgeom(ngrid,plat,plon,parea)
     34
     35         implicit none
     36         INTEGER,INTENT(IN) :: ngrid ! number of atmospheric columns
     37         REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
     38         EXTERNAL SSUM
     39         REAL SSUM
     40         integer :: ig
     41
     42         ! fill "comgeomfi_h" data
     43         call SCOPY(ngrid,plon,1,long,1)
     44         call SCOPY(ngrid,plat,1,lati,1)
     45         call SCOPY(ngrid,parea,1,area,1)
     46         totarea=SSUM(ngrid,area,1)
    4447         DO ig=1,ngrid
    4548            sinlat(ig)=sin(lati(ig))
     
    4851            coslon(ig)=cos(long(ig))
    4952         ENDDO
    50          end subroutine ini_sincosgeom
     53
     54         end subroutine ini_fillgeom
    5155
    5256       end module comgeomfi_h
  • trunk/LMDZ.MARS/libf/phymars/conf_phys.F

    r1226 r1233  
    2727!
    2828!    nq                    Number of tracers
    29 !    pdayref               Day of reference for the simulation
    30 !    pday                  Number of days counted from the North. Spring
    31 !                          equinoxe.
    3229!
    3330!=======================================================================
  • trunk/LMDZ.MARS/libf/phymars/iniphysiq.F90

    r1226 r1233  
    1616                       rlatd ! latitudes
    1717use infotrac, only : nqtot ! number of advected tracers
     18use comgeomfi_h, only: ini_fillgeom
    1819
    1920implicit none
     
    7071! and do some initializations
    7172call phys_state_var_init(klon_omp,nlayer,nqtot, &
    72                          rlatd,rlond,airephy, &
    7373                         punjours,ptimestep,prad,pg,pr,pcpp)
     74call ini_fillgeom(ngrid,rlatd,rlond,airephy)
    7475call conf_phys(nqtot)
    7576
  • trunk/LMDZ.MARS/libf/phymars/meso_inc/meso_inc_var.F

    r1112 r1233  
    1       INTEGER wday_ini
    2       REAL wtsurf(ngrid)  ! input only ay firstcall - output
    3       REAL wtsoil(ngrid,nsoilmx)
    4       REAL wisoil(ngrid,nsoilmx)  !! new soil scheme
    5       REAL wdsoil(ngrid,nsoilmx)   !! new soil scheme
    6       REAL wco2ice(ngrid)
    7       REAL wemis(ngrid)
    8       REAL wqsurf(ngrid,nq)
    9       REAL wq2(ngrid,nlayermx+1)
    10       REAL wwstar(ngrid)
    11       REAL wfluxrad(ngrid)
    121      REAL output_tab2d(ngrid,n2d)
    132      REAL output_tab3d(ngrid,nlayer,n3d)
     
    165      LOGICAL flag_LES     !! pour LES avec isfflx!=0
    176      REAL qsurfice(ngrid) !! pour diagnostics
    18       real alpha,lay1 ! coefficients for building layers
    19       integer iloop
    207      INTEGER tracerset    !!! this corresponds to config%mars
    21       CHARACTER (len=20) :: wtnom(nq) ! tracer name
    228
    239      !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! JF
  • trunk/LMDZ.MARS/libf/phymars/newstart.F

    r1232 r1233  
    3333      use dimradmars_mod, only: tauscaling
    3434      use turb_mod, only: q2
     35      use comgeomfi_h, only: ini_fillgeom
     36
    3537      implicit none
    3638
     
    387389!      'datafile' path may be changed by user)
    388390      call phys_state_var_init(ngridmx,llm,nqtot,
    389      .                         latfi,lonfi,airefi,
    390391     .                         daysec,dtphys,rad,g,r,cpp)
     392      call ini_fillgeom(ngrid,latfi,lonfi,airefi)
    391393      call conf_phys(nqtot)
    392394
  • trunk/LMDZ.MARS/libf/phymars/orbite.F

    r1226 r1233  
    3737c ----------
    3838
    39       REAL pday,pdist_sol,pdecli,pls,i
     39      REAL pdist_sol,pdecli,pls,i
    4040
    4141c-----------------------------------------------------------------------
  • trunk/LMDZ.MARS/libf/phymars/phys_state_var_init.F

    r1226 r1233  
    1       SUBROUTINE phys_state_var_init(ngrid
    2      .               ,nlayer,nq,plat,plon,parea
     1      SUBROUTINE phys_state_var_init(ngrid,nlayer,nq
    32     .               ,pdaysec,ptimestep,prad,pg,pr,pcpp)
    43
     
    3433      use surfdat_h, only: ini_surfdat_h
    3534      use comgeomfi_h, only: ini_comgeomfi_h
    36      .                       ,long,lati,area,totarea
    37      .                       ,ini_sincosgeom
    3835      use comsoil_h, only: ini_comsoil_h
    3936      use dimradmars_mod, only: ini_dimradmars_mod
     
    4845     
    4946      INTEGER,INTENT(IN) :: ngrid,nlayer,nq
    50       REAL,INTENT(IN) :: plat(ngrid),plon(ngrid),parea(ngrid)
    5147      REAL,INTENT(IN) :: pdaysec,ptimestep,prad,pg,pr,pcpp
    5248      EXTERNAL SSUM
     
    7773      ! allocate "comgeomfi_h" arrays
    7874      call ini_comgeomfi_h(ngrid)
    79       ! fill "comgeomfi_h" data
    80       call SCOPY(ngrid,plon,1,long,1)
    81       call SCOPY(ngrid,plat,1,lati,1)
    82       call SCOPY(ngrid,parea,1,area,1)
    83       totarea=SSUM(ngrid,area,1)
    84       ! create sin cos lat lon arrays
    85       ! -- previously in comdiurn
    86       CALL ini_sincosgeom(ngrid)
    8775
    8876      ! allocate "comsoil_h" arrays
  • trunk/LMDZ.MARS/libf/phymars/physiq.F

    r1229 r1233  
    88     $            ,pdu,pdv,pdt,pdq,pdpsrf,tracerdyn
    99#ifdef MESOSCALE
    10 #include "meso_inc/meso_inc_invar.F"
     10     $            ,output_tab2d, output_tab3d, flag_LES
    1111#endif
    1212     $            )
     
    206206c Local saved variables:
    207207c ----------------------
    208       INTEGER,SAVE :: day_ini  ! Initial date of the run (sol since Ls=0)
     208      INTEGER,SAVE :: day_ini ! Initial date of the run (sol since Ls=0)
    209209      INTEGER,SAVE :: icount     ! counter of calls to physiq during the run.
    210210     
     
    393393         fluxrad(:)=0
    394394         wstar(:)=0.
    395 #else
    396 #include "meso_inc/meso_inc_ini_restart.F"
    397395#endif
    398396
     
    400398c        ~~~~~~~~~~~~
    401399#ifndef MESOSCALE
    402 ! Read netcdf initial physical parameters.
     400! GCM. Read netcdf initial physical parameters.
    403401         CALL phyetat0 ("startfi.nc",0,0,
    404402     &         nsoilmx,ngrid,nlayer,nq,
    405403     &         day_ini,time_phys,
    406404     &         tsurf,tsoil,emis,q2,qsurf,co2ice,tauscaling)
    407 #else
    408 #include "meso_inc/meso_inc_ini.F"
    409 #endif
    410405
    411406         if (pday.ne.day_ini) then
     
    418413
    419414         write (*,*) 'In physiq day_ini =', day_ini
     415
     416#else
     417! MESOSCALE. Supposedly everything is already set in modules.
     418! So we just check. And we calculate day_ini + two param in dyn3d/control_mod.
     419      print*,"check: rad,cpp,g,r,rcp,daysec"
     420      print*,rad,cpp,g,r,rcp,daysec
     421      PRINT*,'check: tsurf ',tsurf(1),tsurf(ngrid)
     422      PRINT*,'check: tsoil ',tsoil(1,1),tsoil(ngrid,nsoilmx)
     423      PRINT*,'check: inert ',inertiedat(1,1),inertiedat(ngrid,nsoilmx)
     424      PRINT*,'check: midlayer,layer ', mlayer(:),layer(:)
     425      PRINT*,'check: tracernames ', noms
     426      PRINT*,'check: emis ',emis(1),emis(ngrid)
     427      PRINT*,'check: q2 ',q2(1,1),q2(ngrid,nlayermx+1)
     428      PRINT*,'check: qsurf ',qsurf(1,1),qsurf(ngrid,nq)
     429      PRINT*,'check: co2 ',co2ice(1),co2ice(ngrid)
     430      day_step=daysec/ptimestep
     431      PRINT*,'Call to LMD physics:',day_step,' per Martian day'
     432      iphysiq=ptimestep
     433      day_ini = pday
     434#endif
    420435
    421436c        initialize tracers
     
    13731388c  10. Write output files
    13741389c  ----------------------
    1375 
    1376 c Save variables for eventual restart in MMM and LES
    1377 #ifdef MESOSCALE
    1378 #include "meso_inc/meso_inc_save_restart.F"
    1379 #endif
    13801390
    13811391c    -------------------------------
     
    18811891      !!! OUTPUT FIELDS
    18821892      !!!
    1883       wtsurf(1:ngrid) = tsurf(1:ngrid)    !! surface temperature
    1884       wco2ice(1:ngrid) = co2ice(1:ngrid)  !! co2 ice
     1893      !wtsurf(1:ngrid) = tsurf(1:ngrid)    !! surface temperature
     1894      !wco2ice(1:ngrid) = co2ice(1:ngrid)  !! co2 ice
    18851895      TAU_lay(:)=tau(:,1)!!true opacity (not a reference like tauref)
    18861896      IF (tracer) THEN
  • trunk/LMDZ.MARS/libf/phymars/testphys1d.F

    r1229 r1233  
    55      use infotrac, only: nqtot, tname
    66      use comsoil_h, only: volcapa, layer, mlayer, inertiedat, nsoilmx
    7       use comgeomfi_h, only: lati, long, area, sinlat
     7      use comgeomfi_h, only: lati, long, area, sinlat, ini_fillgeom
     8
    89      use surfdat_h, only: albedodat, z0_default, emissiv, emisice,
    910     &                     albedice, iceradius, dtemisice, z0,
     
    480481!Mars possible matter with dtphys in input and include!!!
    481482      call phys_state_var_init(1,llm,nq,
    482      .          latitude,longitude,1.0,
    483483     .          daysec,dtphys,rad,g,r,cpp)
     484      call ini_fillgeom(1,latitude,longitude,1.0)
    484485      call conf_phys(nq)
    485486
Note: See TracChangeset for help on using the changeset viewer.