Changeset 270


Ignore:
Timestamp:
09/05/14 14:42:27 (10 years ago)
Author:
millour
Message:

Added features for the Saturn case:

  • Added possibility to run without startfi or restartfi.nc files
  • Added reference temperature "temp_profile.txt" profile to start from
  • More XIOS outputs, and put them on "presnivs (pressure) vertical coordinate
  • Added "-openmp-threadprivate compat" OpenMP option in Ada arch file

EM

Location:
codes/icosagcm/branches/SATURN_DYNAMICO
Files:
1 added
9 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/arch/arch-X64_ADA.fcm

    r264 r270  
    1111%DEBUG_FFLAGS        -g -traceback -check bounds -fp-model strict 
    1212%MPI_FFLAGS 
    13 %OMP_FFLAGS          -openmp 
     13%OMP_FFLAGS          -openmp -openmp-threadprivate compat 
    1414%BASE_LD             -i4 -r8 -auto ${MKL_LIBS} -L/smplocal/pub/FFTW/3.3.3_dyn/lib -lfftw3 -lmkl_intel_lp64 -lmkl_sequential -lmkl_core -lpthread -Wl,-rpath=/smplocal/pub/NetCDF/4.1.3/mpi/lib:/smplocal/pub/HDF5/1.8.9/par/lib:/smplocal/pub/FFTW/3.3.3_dyn/lib -L../../LMDZ.COMMON/lib -llmdz  
    1515%MPI_LD 
  • codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/compile_dynlmdz_ada

    r264 r270  
    11cd ../LMDZ.COMMON 
    2 rm -rf libo 
    3 ./makelmdz_fcm -s 1 -d 128x96x64 -b 20x30 -io none -arch X64_ADA -parallel mpi -p std -j 8 gcm 
     2#rm -rf libo 
     3./makelmdz_fcm -s 1 -d 32x24x64 -b 20x30 -io none -arch X64_ADA -parallel mpi -p std -j 8 -full gcm 
    44cd ../ICOSAGCM 
    55rm bin/icosa_gcm.exe 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/iostart.F90

    r245 r270  
    4444CONTAINS 
    4545 
    46   SUBROUTINE open_startphy(filename) 
     46  SUBROUTINE open_startphy(filename,found) 
    4747  USE netcdf, only: NF90_OPEN, NF90_NOERR, NF90_NOWRITE, nf90_strerror 
    4848  USE mod_phys_lmdz_para, only: is_master, bcast 
    4949  IMPLICIT NONE 
    50     CHARACTER(LEN=*) :: filename 
     50    CHARACTER(LEN=*),INTENT(IN) :: filename 
     51    LOGICAL,INTENT(OUT),OPTIONAL   :: found  
    5152    INTEGER          :: ierr 
    5253 
     
    5657        write(*,*)'open_startphy: problem opening file '//trim(filename) 
    5758        write(*,*)trim(nf90_strerror(ierr)) 
    58         CALL ABORT 
     59        !CALL ABORT 
     60        found=.false. 
     61      ELSE 
     62        found=.true. 
    5963      ENDIF 
    6064    ENDIF 
    6165     
    6266    CALL bcast(nid_start) ! tell all procs about nid_start 
     67    if(present(found)) CALL bcast(found) 
    6368   
    6469  END SUBROUTINE open_startphy 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/phyetat0_academic.F90

    r269 r270  
    8383       
    8484      INTEGER :: indextime=1 ! index of selected time, default value=1 
    85       logical :: found 
     85      logical :: found,found_file 
    8686 
    8787! 
     
    9898 
    9999! open physics initial state file: 
    100 call open_startphy(fichnom) 
    101  
    102  
    103 ! possibility to modify tab_cntrl in tabfi 
    104 write(*,*) 
    105 write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0 
    106 call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, & 
     100call open_startphy(fichnom,found_file) 
     101 
     102! Ehouarn, if file not found, then call tabfi with nid_start==0 
     103if (.not.found_file) then 
     104  write(*,*) 'phyetat0_academic: call tabfi with nid_start=0' 
     105  call tabfi (ngrid,0,Lmodif,tab0,day_ini,lmax,p_rad, & 
    107106                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time) 
    108  
     107else 
     108  ! possibility to modify tab_cntrl in tabfi 
     109  write(*,*) 
     110  write(*,*) 'TABFI in phyeta0: Lmodif=',Lmodif," tab0=",tab0 
     111  call tabfi (ngrid,nid_start,Lmodif,tab0,day_ini,lmax,p_rad, & 
     112                   p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time) 
     113endif 
    109114!c 
    110115!c Lecture des latitudes (coordonnees): 
     
    165170 
    166171! Load surface geopotential: 
    167 call get_field("phisfi",phisfi,found) 
     172if (found_file) then 
     173  call get_field("phisfi",phisfi,found) 
     174else 
     175  found=.false. 
     176endif 
    168177if (.not.found) then 
    169178  write(*,*) "phyetat0: Failed loading <phisfi>" 
     
    175184 
    176185! Load bare ground albedo: 
    177 call get_field("albedodat",albedodat,found) 
     186if (found_file) then 
     187  call get_field("albedodat",albedodat,found) 
     188else 
     189  found=.false. 
     190endif 
    178191if (.not.found) then 
    179192  write(*,*) "phyetat0: Failed loading <albedodat>" 
     
    187200 
    188201! ZMEA 
    189 call get_field("ZMEA",zmea,found) 
     202if (found_file) then 
     203  call get_field("ZMEA",zmea,found) 
     204else 
     205  found=.false. 
     206endif 
    190207if (.not.found) then 
    191208    zmea(:)=0. 
     
    196213 
    197214! ZSTD 
    198 call get_field("ZSTD",zstd,found) 
     215if (found_file) then 
     216  call get_field("ZSTD",zstd,found) 
     217else 
     218  found=.false. 
     219endif 
    199220if (.not.found) then 
    200221  write(*,*) "phyetat0: Failed loading <ZSTD>" 
     
    206227 
    207228! ZSIG 
    208 call get_field("ZSIG",zsig,found) 
     229if (found_file) then 
     230  call get_field("ZSIG",zsig,found) 
     231else 
     232  found=.false. 
     233endif 
    209234if (.not.found) then 
    210235  write(*,*) "phyetat0: Failed loading <ZSIG>" 
     
    216241 
    217242! ZGAM 
    218 call get_field("ZGAM",zgam,found) 
     243if (found_file) then 
     244  call get_field("ZGAM",zgam,found) 
     245else 
     246  found=.false. 
     247endif 
    219248if (.not.found) then 
    220249  write(*,*) "phyetat0: Failed loading <ZGAM>" 
     
    226255 
    227256! ZTHE 
    228 call get_field("ZTHE",zthe,found) 
     257if (found_file) then 
     258  call get_field("ZTHE",zthe,found) 
     259else 
     260  found=.false. 
     261endif 
    229262if (.not.found) then 
    230263  write(*,*) "phyetat0: Failed loading <ZTHE>" 
     
    236269 
    237270! Surface temperature : 
    238 call get_field("tsurf",tsurf,found,indextime) 
    239 if (.not.found) then 
    240   write(*,*) "phyetat0: Failed loading <tsurf>" 
    241 !mi initialising tsurf with pt(:,1)  
    242 !tsurf(:)=175.0 
     271if (found_file) then 
     272  call get_field("tsurf",tsurf,found,indextime) 
     273else 
     274  found=.false. 
     275endif 
     276if (.not.found) then 
     277  !mi initialising tsurf with pt(:,1) 
     278  !tsurf(:)=175.0 
    243279else 
    244280  write(*,*) "phyetat0: Surface temperature <tsurf> range:", & 
     
    247283 
    248284! Surface emissivity 
    249 call get_field("emis",emis,found,indextime) 
     285if (found_file) then 
     286  call get_field("emis",emis,found,indextime) 
     287else 
     288  found=.false. 
     289endif 
    250290if (.not.found) then 
    251291  write(*,*) "phyetat0: Failed loading <emis>" 
     
    257297 
    258298! Cloud fraction (added by BC 2010) 
    259 call get_field("cloudfrac",cloudfrac,found,indextime) 
     299if (found_file) then 
     300  call get_field("cloudfrac",cloudfrac,found,indextime) 
     301else 
     302  found=.false. 
     303endif 
    260304if (.not.found) then 
    261305  write(*,*) "phyetat0: Failed loading <cloudfrac>" 
     
    267311 
    268312! Total cloud fraction (added by BC 2010) 
    269 call get_field("totcloudfrac",totcloudfrac,found,indextime) 
     313if (found_file) then 
     314  call get_field("totcloudfrac",totcloudfrac,found,indextime) 
     315else 
     316  found=.false. 
     317endif 
    270318if (.not.found) then 
    271319  write(*,*) "phyetat0: Failed loading <totcloudfrac>" 
     
    277325 
    278326! Height of oceanic ice (added by BC 2010) 
    279 call get_field("hice",hice,found,indextime) 
     327if (found_file) then 
     328  call get_field("hice",hice,found,indextime) 
     329else 
     330  found=.false. 
     331endif 
    280332if (.not.found) then 
    281333  write(*,*) "phyetat0: Failed loading <hice>" 
     
    291343! SLAB OCEAN (added by BC 2014) 
    292344! nature of the surface 
    293 call get_field("rnat",rnat,found,indextime) 
     345if (found_file) then 
     346  call get_field("rnat",rnat,found,indextime) 
     347else 
     348  found=.false. 
     349endif 
    294350if (.not.found) then 
    295351  write(*,*) "phyetat0: Failed loading <rnat>" 
     
    310366endif 
    311367! Pourcentage of sea ice cover 
    312 call get_field("pctsrf_sic",pctsrf_sic,found,indextime) 
     368if (found_file) then 
     369  call get_field("pctsrf_sic",pctsrf_sic,found,indextime) 
     370else 
     371  found=.false. 
     372endif 
    313373if (.not.found) then 
    314374  write(*,*) "phyetat0: Failed loading <pctsrf_sic>" 
     
    321381endif 
    322382! Slab ocean temperature (2 layers) 
    323 call get_field("tslab",tslab,found,indextime) 
     383if (found_file) then 
     384  call get_field("tslab",tslab,found,indextime) 
     385else 
     386  found=.false. 
     387endif 
    324388if (.not.found) then 
    325389  write(*,*) "phyetat0: Failed loading <tslab>" 
     
    334398endif 
    335399! Oceanic ice temperature 
    336 call get_field("tsea_ice",tsea_ice,found,indextime) 
     400if (found_file) then 
     401  call get_field("tsea_ice",tsea_ice,found,indextime) 
     402else 
     403  found=.false. 
     404endif 
    337405if (.not.found) then 
    338406  write(*,*) "phyetat0: Failed loading <tsea_ice>" 
     
    345413endif 
    346414!  Oceanic ice quantity (kg/m^2) 
    347 call get_field("sea_ice",sea_ice,found,indextime) 
     415if (found_file) then 
     416  call get_field("sea_ice",sea_ice,found,indextime) 
     417else 
     418  found=.false. 
     419endif 
    348420if (.not.found) then 
    349421  write(*,*) "phyetat0: Failed loading <sea_ice>" 
     
    360432 
    361433! pbl wind variance 
    362 call get_field("q2",q2,found,indextime) 
     434if (found_file) then 
     435  call get_field("q2",q2,found,indextime) 
     436else 
     437  found=.false. 
     438endif 
    363439if (.not.found) then 
    364440  write(*,*) "phyetat0: Failed loading <q2>" 
     
    380456                           ' h2o_ice instead of h2o_vap' 
    381457    endif 
    382     call get_field(txt,qsurf(:,iq),found,indextime) 
     458    if (found_file) then 
     459      call get_field(txt,qsurf(:,iq),found,indextime) 
     460    else 
     461      found=.false. 
     462    endif 
    383463    if (.not.found) then 
    384464      write(*,*) "phyetat0: Failed loading <",trim(txt),">" 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/physiq.F90

    r269 r270  
    569569!ym               rnat,pctsrf_sic,tslab, tsea_ice,sea_ice) 
    570570 
     571         write(*,*) "physiq: firstcall, call phyetat0_academic" 
    571572         call phyetat0_academic(ngrid,nlayer,"startfi.nc",0,0,nsoilmx,nq,   & 
    572573               day_ini,time_phys,tsurf,tsoil,emis,q2,qsurf,   & 
     
    575576 
    576577!mi initialising tsurf with pt 
     578         write(*,*) "Physiq: initializing tsurf(:) to pt(:,1) !!" 
    577579         tsurf(:)=pt(:,1) 
    578580 
     
    744746 
    745747         if (ngrid.ne.1) then ! no need to create a restart file in 1d 
    746            call physdem0("restartfi.nc",long,lati,nsoilmx,ngrid,nlayer,nq, & 
    747                          ptimestep,pday+nday,time_phys,area, & 
    748                          albedodat,inertiedat,zmea,zstd,zsig,zgam,zthe) 
     748! EM: No restart file (for now). 
     749!           call physdem0("restartfi.nc",long,lati,nsoilmx,ngrid,nlayer,nq, & 
     750!                         ptimestep,pday+nday,time_phys,area, & 
     751!                         albedodat,inertiedat,zmea,zstd,zsig,zgam,zthe) 
    749752         endif 
    750753          
     
    19721975!                    cloudfrac,totcloudfrac,hice,noms) 
    19731976!#endif 
    1974               call physdem1("restartfi.nc",nsoilmx,ngrid,nlayer,nq, & 
    1975                       ptimestep,ztime_fin, & 
    1976                       tsurf,tsoil,emis,q2,qsurf_hist, & 
    1977                       cloudfrac,totcloudfrac,hice, & 
    1978                       rnat,pctsrf_sic,tslab,tsea_ice,sea_ice) 
     1977 
     1978! EM: do not write a restart file (for now). 
     1979!              call physdem1("restartfi.nc",nsoilmx,ngrid,nlayer,nq, & 
     1980!                      ptimestep,ztime_fin, & 
     1981!                      tsurf,tsoil,emis,q2,qsurf_hist, & 
     1982!                      cloudfrac,totcloudfrac,hice, & 
     1983!                      rnat,pctsrf_sic,tslab,tsea_ice,sea_ice) 
    19791984            endif 
    19801985 
     
    22392244      CALL write_xios_field("ASR",fluxabs_sw) 
    22402245      CALL write_xios_field("OLR",fluxtop_lw) 
     2246      call write_xios_field("input_temp",pt) 
     2247      call write_xios_field("input_u",pu) 
     2248      call write_xios_field("input_v",pv) 
     2249      call write_xios_field("dtrad",dtrad) 
     2250      call write_xios_field("zdtlw",zdtlw) 
     2251      call write_xios_field("zdtsw",zdtsw) 
     2252      call write_xios_field("zdtdyn",zdtdyn/ptimestep) 
     2253      call write_xios_field("zdtdif",zdtdif) 
     2254      call write_xios_field("zdtadj",zdtadj) 
     2255      call write_xios_field("pdt",pdt) 
    22412256      IF (lastcall) CALL finalize_xios_output 
    22422257       
     
    23442359      endif 
    23452360 
     2361      write(*,*) "physiq: done, zday=",zday 
    23462362      return 
    23472363    end subroutine physiq 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/tabfi.F

    r227 r270  
    4444c======================================================================= 
    4545! to use  'getin' 
    46       use ioipsl_getincom , only: getin 
     46      use ioipsl_getincom_p , only: getin_p 
    4747 
    4848      use surfdat_h, only: albedice, emisice, iceradius, dtemisice, 
     
    8888c  Initialization of various physical constants to defaut values (nid = 0 case) 
    8989c----------------------------------------------------------------------- 
     90        ! Ehouarn: Default Saturn values: 
     91        tab_cntrl(:)=0 
     92        write(*,*) "Using default Saturn values..." 
     93        ! these should be read in a def file I guess... 
     94        lmax=0 ! not used anyways 
     95        !day_ini=0 
     96        time=0 
     97        ! radius of the planet 
     98        rad=60268000 
     99        call getin_p("radius",rad) 
     100        ! Planetary rotation rate 
     101        omeg=0.00016512100410182 
     102        call getin_p("omega",omeg) 
     103        ! Gravity 
     104        g=10.44 
     105        call getin_p("g",g) 
     106        !mugaz=2.34 !EM: does not give cpp=11500 
     107        mugaz=2.53 ! with this value of mugaz, cpp=11500 
     108        call getin_p("mugaz",mugaz) 
     109        ! kappa 
     110        rcp=0.2857143 
     111        call getin_p("kappa",rcp) 
     112        cpp=(8.314511/(mugaz/1000.0))/rcp 
     113        call getin_p("cpp",cpp) 
     114!        write(*,*) "tabfi: cpp=",cpp 
     115        ! length (s) of a "standard" day 
     116        daysec=38052 
     117        call getin_p("day_length",daysec) 
     118        ! physics time step (s) ! not sure we need this here 
     119        dtphys=19026 
     120        ! length of year, in standard days 
     121        year_day=24430 
     122        ! Orbital parameters 
     123        periastr=9.02151966094971 
     124        apoastr=10.054479598999 
     125        peri_day=19280 
     126        obliquit=26.7299995422363 
     127        ! Other parameters some physical paréametrizations need 
     128        z0=1e-2 
     129        lmixmin=30 
     130        emin_turb=1.e-6 
     131        albedice(:)=0 
     132        emisice(:)=0 
     133        emissiv=0 
     134        iceradius(:)=1.e-6 
     135        dtemisice(:)=0 
     136        volcapa=1000000 
     137c----------------------------------------------------------------------- 
     138c       Save some constants for later use (as routine arguments) 
     139c----------------------------------------------------------------------- 
     140        p_omeg = omeg 
     141        p_g = g 
     142        p_cpp = cpp 
     143        p_mugaz = mugaz 
     144        p_daysec = daysec 
     145        p_rad=rad 
     146 
    90147      ELSE 
    91148c----------------------------------------------------------------------- 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/xios_output.F90

    r263 r270  
    2020  USE mod_phys_lmdz_para 
    2121  USE mod_grid_phy_lmdz 
     22  USE planete_mod, ONLY: ap,bp,preff 
    2223   
    2324  IMPLICIT NONE 
     
    3334    REAL :: bounds_lat_mpi(klon_mpi,nvertex) 
    3435    INTEGER :: l 
     36    REAL :: presnivs(klev) 
    3537 
    3638    CALL gather_omp(rlond,lon_mpi) 
     
    4547    CALL xios_set_current_context(ctx_hdl) 
    4648    
    47     lev_value(:) = (/ (l,l=1,klev) /)      
     49!    lev_value(:) = (/ (l,l=1,klev) /)      
     50!    CALL xios_set_axis_attr("altitude",size=klev ,value=lev_value) 
    4851     
    49     CALL xios_set_axis_attr("altitude",size=klev ,value=lev_value) 
    50      
     52    ! build presnivs "pseudo-pressure" at mid-layers 
     53    DO l=1,klev 
     54      presnivs(l)=0.5*(ap(l)+bp(l)*preff+ap(l+1)+bp(l+1)*preff) 
     55    ENDDO 
     56    CALL xios_set_axis_attr("presnivs",size=klev,value=presnivs,unit="Pa",positive="down") 
    5157   
    5258    CALL xios_set_domain_attr("horiz_domain",ni_glo=klon_glo, ibegin=klon_mpi_begin, ni=klon_mpi) 
  • codes/icosagcm/branches/SATURN_DYNAMICO/TEST/lmdz_physics.xml

    r264 r270  
    1313     <field id="OLR"    long_name="outgoing longwave rad."      unit="W m-2"/> 
    1414      
    15      <field_group axis_ref="altitude"> 
     15     <field_group axis_ref="presnivs"> 
    1616       <field id="temp" long_name="temperature"                 unit="K"/> 
    1717       <field id="u"    long_name="Zonal wind"                  unit="m.s-1"/> 
    1818       <field id="v"    long_name="Meridional wind"             unit="m.s-1"/> 
    1919       <field id="p"    long_name="Pressure"                    unit="Pa"/> 
     20       <field id="input_temp" long_name="Input temperature"  unit="K"/> 
     21       <field id="input_u" long_name="Input zonal wind"  unit="m/s"/> 
     22       <field id="input_v" long_name="Input meridional wind"  unit="m/s"/> 
     23       <field id="dtrad" long_name="Total radiative tendency" unit="K/s"/> 
     24       <field id="zdtlw" long_name="LW radiative tendency" unit="K/s"/> 
     25       <field id="zdtsw" long_name="SW radiative tendency" unit="K/s"/> 
     26       <field id="zdtdyn" long_name="Dyn temperature tendency" unit="K/s"/> 
     27       <field id="zdtdif" long_name="Turbulent diffusion tendency" unit="K/s"/> 
     28       <field id="zdtadj" long_name="Convective adjustement tendency" unit="K/s"/> 
     29       <field id="pdt" long_name="Total temperature tendency" unit="K/s"/> 
    2030     </field_group>  
    2131      
     
    2333     
    2434     
    25    <file_definition type="one_file" par_access="collective" output_freq="10ts" sync_freq="10ts" output_level="10" enabled=".TRUE."> 
     35   <file_definition type="one_file" par_access="collective" output_freq="1ts" sync_freq="1ts" output_level="10" enabled=".TRUE."> 
    2636 
    2737     <file id="xios_diagfi" name="xios_diagfi" >  
     
    3444     
    3545     
     46<!--   <axis_definition> 
     47     <axis id="altitude"/> 
     48   </axis_definition> --> 
    3649   <axis_definition> 
    37      <axis id="altitude"/> 
     50     <axis id="presnivs"/> 
    3851   </axis_definition> 
    3952     
  • codes/icosagcm/branches/SATURN_DYNAMICO/TEST/run_icosa.def

    r256 r270  
    99 
    1010# Number of subdivision on a main triangle (nbp) : integer (default=40) 
    11 nbp=40 
     11nbp=10 
    1212 
    1313# nbp                 20  40  80 160 
     
    4848itau_adv=3 
    4949 
    50 # number of timestep (default 100) 
     50# number of timestep (default 100) (ignored if run_length is set) 
    5151 itaumax = 100 
    5252 
     
    5555#run_length=0 
    5656#run_length=432000 
    57 # one saturn year 
    58 run_length=929610360 
     57# one saturn year (24430 days) 
     58#run_length=929610360 
     59# 5 saturn day (5*38052=190260) 
     60#run_length=190260 
     61# 1 saturn day 
     62run_length=38052 
     63# 100 saturn days 
     64#run_length=3805200 
     65# 2000 saturn days 
     66#run_length=76104000 
    5967 
    6068#activate IO (default = true) 
     
    7987# etat0 : initial state : string (default=jablonowsky06) :  
    8088# jablonowsky06, academic, ncar 
    81 etat0=isothermal 
    82 etat0_isothermal_temp=175 
     89#etat0=isothermal 
     90#etat0_isothermal_temp=175 
     91 
     92etat0=temperature_profile 
     93# for 'etat0=temperature_profile" 
     94# initial temperature profile provided in file  
     95temperature_profile_file=temp_profile.txt 
     96 
     97#etat0=start_file 
     98# for 'etat0=start_file" 
     99# start file name (default is start.nc) 
     100# start_file_name=start 
     101# restart file name (default is restart.nc) 
     102#restart_file_name=restart 
     103 
    83104# ------------------------------ Dynamics -------------------------------- 
    84105 
Note: See TracChangeset for help on using the changeset viewer.