Changeset 3562


Ignore:
Timestamp:
Dec 17, 2024, 4:19:04 PM (5 days ago)
Author:
mmaurice
Message:

Generic PCM

1D restart operational: a restart1D.nc file is created that contains
psurf, tracers, winds and temperature profiles. A retartfi.nc file is
also created. Move those to and start1D.nc and startfi.nc and set
"restart" flag to .true. in rcm1d.def to restart from the files (also
make sure that day0 corresponds to the value in startfi.nc).

MM

Location:
trunk/LMDZ.GENERIC/libf/phystd
Files:
1 added
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/phystd/dyn1d/rcm1d.F

    r3515 r3562  
    3838      use phys_state_var_mod, only: phys_state_var_init
    3939      use physiq_mod, only: physiq
     40      use restart1D_mod, only: writerestart1D
     41      use iostart, only: length
     42      use netcdf, only: NF90_OPEN, NF90_NOERR, NF90_NOWRITE,
     43     &                  nf90_strerror,NF90_INQ_VARID, NF90_GET_VAR,
     44     &                  NF90_CLOSE
    4045      implicit none
    4146
     
    7883      INTEGER ilayer,ilevel,isoil,idt,iq
    7984      LOGICAl firstcall,lastcall
     85      LOGICAL restart
     86      INTEGER nid_restart1D, nid_restartfi
     87      INTEGER controleid, uid, vid, tempid, tsurfid, did, tid
     88      INTEGER,ALLOCATABLE :: qid(:), qsurfid(:)
    8089c
    8190      INTEGER day0          ! date initial (sol ; =0 a Ls=0)
     
    122131
    123132      logical oldcompare, earthhack,saveprofile
     133      real controle1D(length)
    124134
    125135!     added by RW for zlay computation
     
    186196        call system("echo 'INCLUDEDEF=rcm1d.def' >> run.def")
    187197      endif
     198
     199! Check restart
     200      call getin("restart",restart)
     201      if (restart) then
     202        ierr = NF90_OPEN('start1D.nc', NF90_NOWRITE, nid_restart1D)
     203        if (ierr.NE.NF90_NOERR) then
     204          write(*,*)'readstart1D: problem opening 1D start file'
     205          write(*,*)trim(nf90_strerror(ierr))
     206          call abort_physic("readstart1D","Cannot open file",1)
     207        endif
     208        ierr = NF90_OPEN('startfi.nc', NF90_NOWRITE, nid_restartfi)
     209        if (ierr.NE.NF90_NOERR) then
     210          write(*,*)'readstart1D: problem opening startfi file'
     211          write(*,*)trim(nf90_strerror(ierr))
     212          call abort_physic("readstart1D","Cannot open file",1)
     213        endif
     214      endif ! restart
    188215
    189216      ! read nq from traceur.def
     
    474501      ENDIF
    475502
    476       psurf = -99999.
    477       PRINT *,'SURFACE PRESSURE in Pa ?'
    478       call getin("psurf",psurf)
    479       IF (psurf.eq.-99999.) THEN
    480           PRINT *,"STOP. I NEED psurf IN RCM1D.DEF."
    481           STOP
    482       ELSE
    483           PRINT *,"--> psurf = ",psurf
    484       ENDIF
     503      if (restart) then
     504        ierr=NF90_INQ_VARID(nid_restart1D,'controle',controleid)
     505        if (ierr==NF90_NOERR) then
     506          ierr=NF90_GET_VAR(nid_restart1D,controleid,controle1D)
     507          if (ierr/=NF90_NOERR) then
     508            PRINT*, 'read restart 1D: Failed loading psurf'
     509            CALL abort_physic("readstart1D","Failed to read variable",1)
     510          endif
     511        endif
     512        psurf = controle1D(1)
     513        PRINT *,"In restart1D.nc, day0=",controle1D(2),
     514     &          " and time=",controle1D(3)
     515        PRINT*,"(These values are NOT used, ",
     516     &         "those given in rcm1d.def are used)"
     517      else ! restart
     518        psurf = -99999.
     519        PRINT *,'SURFACE PRESSURE in Pa ?'
     520        call getin("psurf",psurf)
     521        IF (psurf.eq.-99999.) THEN
     522            PRINT *,"STOP. I NEED psurf IN RCM1D.DEF."
     523            STOP
     524        ELSE
     525            PRINT *,"--> psurf = ",psurf
     526        ENDIF
     527      endif ! restart
    485528      !! we need reference pressures
    486529      pa=psurf/30.
     
    494537c  ------------------------------------
    495538c    Date (en sols depuis le solstice de printemps) du debut du run
    496       day0 = 0 ! default value for day0
    497       write(*,*) 'Initial date (in martian sols ; =0 at Ls=0)?'
    498       call getin("day0",day0)
    499       day=float(day0)
    500       write(*,*) " day0 = ",day0
     539      !if (restart) then
     540      !  ! day   
     541      !  ierr=NF90_INQ_VARID(nid_restart1D,'day',did)
     542      !  if (ierr==NF90_NOERR) then
     543      !    ierr=NF90_GET_VAR(nid_restart1D,did,day)
     544      !    if (ierr/=NF90_NOERR) then
     545      !      PRINT*, 'read restart 1D: Failed loading day'
     546      !      CALL abort_physic("readstart1D","Failed to read variable",1)
     547      !    endif
     548      !  endif
     549
     550      !  ! time
     551      !  ierr=NF90_INQ_VARID(nid_restart1D,'time',tid)
     552      !  if (ierr==NF90_NOERR) then
     553      !    ierr=NF90_GET_VAR(nid_restart1D,tid,time)
     554      !    if (ierr/=NF90_NOERR) then
     555      !      PRINT*, 'read restart 1D: Failed loading time'
     556      !      CALL abort_physic("readstart1D","Failed to read variable",1)
     557      !    endif
     558      !  endif
     559
     560      !else
     561        day0 = 0 ! default value for day0
     562        write(*,*) 'Initial date (in martian sols ; =0 at Ls=0)?'
     563        call getin("day0",day0)
     564        day=float(day0)
     565        write(*,*) " day0 = ",day0
    501566c  Heure de demarrage
    502       time=0 ! default value for time
    503       write(*,*)'Initial local time (in hours, between 0 and 24)?'
    504       call getin("time",time)
    505       write(*,*)" time = ",time
    506       time=time/24.E+0 ! convert time (hours) to fraction of sol
    507 
     567        time=0 ! default value for time
     568        write(*,*)'Initial local time (in hours, between 0 and 24)?'
     569        call getin("time",time)
     570        write(*,*)" time = ",time
     571        time=time/24.E+0 ! convert time (hours) to fraction of sol
     572      !endif
    508573
    509574c  Discretisation (Definition de la grille et des pas de temps)
     
    629694
    630695         do iq=1,nq
     696
     697            if (restart) then
     698              if (iq.eq.1) then
     699                allocate(qid(nq))
     700                allocate(qsurfid(nq))
     701              endif
     702              ! read q
     703              ierr=NF90_INQ_VARID(nid_restart1D,noms(iq),qid(iq))
     704              if (ierr==NF90_NOERR) then
     705                ierr=NF90_GET_VAR(nid_restart1D,qid(iq),q(:,iq),
     706     &           count=(/1,nlayer,1,1/))
     707                if (ierr/=NF90_NOERR) then
     708                  PRINT*, 'read restart 1D: Failed loading ', noms(iq)
     709                  write(*,*)trim(nf90_strerror(ierr))
     710                  CALL abort_physic("readstart1D",
     711     &                              "Failed to read variable",1)
     712                endif
     713              endif
     714              ! read qsurf
     715              ierr=NF90_INQ_VARID(nid_restartfi,noms(iq),qsurfid(iq))
     716              if (ierr==NF90_NOERR) then
     717                ierr=NF90_GET_VAR(nid_restartfi,qsurfid(iq),qsurf(iq))
     718                if (ierr/=NF90_NOERR) then
     719                  PRINT*, 'read restartfi: Failed loading ', noms(iq)
     720                  write(*,*)trim(nf90_strerror(ierr))
     721                  CALL abort_physic("readstartfi",
     722     &                              "Failed to read variable",1)
     723                endif
     724              endif
     725            else ! restart
    631726         
    632             txt=""
    633             write(txt,"(a)") tname(iq)
    634             write(*,*)"  tracer:",trim(txt)
     727              txt=""
     728              write(txt,"(a)") tname(iq)
     729              write(*,*)"  tracer:",trim(txt)
    635730             
    636             ! CO2
    637             if (txt.eq."co2_ice") then
    638                q(:,iq)=0.   ! kg/kg of atmosphere
    639                qsurf(iq)=0. ! kg/m2 at the surface               
    640                ! Look for a "profile_co2_ice" input file
    641                open(91,file='profile_co2_ice',status='old',
    642      &         form='formatted',iostat=ierr)
    643                if (ierr.eq.0) then
    644                   read(91,*) qsurf(iq)
    645                   do ilayer=1,nlayer
    646                      read(91,*) q(ilayer,iq)
    647                   enddo
    648                else
    649                   write(*,*) "No profile_co2_ice file!"
    650                endif
    651                close(91)
    652             endif ! of if (txt.eq."co2")
     731              ! CO2
     732              if (txt.eq."co2_ice") then
     733                 q(:,iq)=0.   ! kg/kg of atmosphere
     734                 qsurf(iq)=0. ! kg/m2 at the surface               
     735                 ! Look for a "profile_co2_ice" input file
     736                 open(91,file='profile_co2_ice',status='old',
     737     &           form='formatted',iostat=ierr)
     738                 if (ierr.eq.0) then
     739                    read(91,*) qsurf(iq)
     740                    do ilayer=1,nlayer
     741                       read(91,*) q(ilayer,iq)
     742                    enddo
     743                 else
     744                    write(*,*) "No profile_co2_ice file!"
     745                 endif
     746                 close(91)
     747              endif ! of if (txt.eq."co2")
    653748         
    654             ! WATER VAPOUR
    655             if (txt.eq."h2o_vap") then
    656                q(:,iq)=0.   ! kg/kg of atmosphere
    657                qsurf(iq)=0. ! kg/m2 at the surface
    658                ! Look for a "profile_h2o_vap" input file   
    659                open(91,file='profile_h2o_vap',status='old',
    660      &         form='formatted',iostat=ierr)
    661                if (ierr.eq.0) then
    662                   read(91,*) qsurf(iq)
    663                   do ilayer=1,nlayer
    664                      read(91,*) q(ilayer,iq)
    665                   enddo
    666                else
    667                   write(*,*) "No profile_h2o_vap file!"
    668                endif
    669                close(91)
    670             endif ! of if (txt.eq."h2o_vap")
     749              ! WATER VAPOUR
     750              if (txt.eq."h2o_vap") then
     751                 q(:,iq)=0.   ! kg/kg of atmosphere
     752                 qsurf(iq)=0. ! kg/m2 at the surface
     753                 ! Look for a "profile_h2o_vap" input file   
     754                 open(91,file='profile_h2o_vap',status='old',
     755     &           form='formatted',iostat=ierr)
     756                 if (ierr.eq.0) then
     757                    read(91,*) qsurf(iq)
     758                    do ilayer=1,nlayer
     759                       read(91,*) q(ilayer,iq)
     760                    enddo
     761                 else
     762                    write(*,*) "No profile_h2o_vap file!"
     763                 endif
     764                 close(91)
     765              endif ! of if (txt.eq."h2o_vap")
    671766           
    672             ! WATER ICE
    673             if (txt.eq."h2o_ice") then
    674                q(:,iq)=0.   ! kg/kg of atmosphere
    675                qsurf(iq)=0. ! kg/m2 at the surface
    676                ! Look for a "profile_h2o_ice" input file
    677                open(91,file='profile_h2o_ice',status='old',
    678      &         form='formatted',iostat=ierr)
    679                if (ierr.eq.0) then
    680                   read(91,*) qsurf(iq)
    681                   do ilayer=1,nlayer
    682                      read(91,*) q(ilayer,iq)
    683                   enddo
    684                else
    685                   write(*,*) "No profile_h2o_ice file!"
    686                endif
    687                close(91)
    688             endif ! of if (txt.eq."h2o_ice")
    689 
    690             !_vap
    691             if((txt .ne. 'h2o_vap') .and.
    692      &                     (index(txt,'_vap'   ) .ne. 0))   then
    693                   q(:,iq)=0. !kg/kg of atmosphere
    694                   qsurf(iq) = 0. !kg/kg of atmosphere
    695                   ! Look for a "profile_...._vap" input file
    696                   tracer_profile_file_name=""
    697                   tracer_profile_file_name='profile_'//txt
    698                   open(91,file=tracer_profile_file_name,status='old',
    699      &            form="formatted",iostat=ierr)
    700                   if (ierr .eq. 0) then
    701                         read(91,*)qsurf(iq)
    702                         do ilayer=1,nlayer
    703                               read(91,*)q(ilayer,iq)
    704                         enddo
    705                   else
    706                         write(*,*) "No initial profile "
    707                         write(*,*) " for this tracer :"
    708                         write(*,*) txt
    709                   endif
    710                   close(91)
    711             endif ! (txt .eq. "_vap")
    712             !_ice
    713             if((txt.ne."h2o_ice") .and.
    714      &                      (index(txt,'_ice'   ) /= 0)) then
    715                   q(:,iq)=0. !kg/kg of atmosphere
    716                   qsurf(iq) = 0. !kg/kg of atmosphere
    717             endif ! we only initialize the solid at 0
    718          enddo ! of do iq=1,nq
    719          
     767              ! WATER ICE
     768              if (txt.eq."h2o_ice") then
     769                 q(:,iq)=0.   ! kg/kg of atmosphere
     770                 qsurf(iq)=0. ! kg/m2 at the surface
     771                 ! Look for a "profile_h2o_ice" input file
     772                 open(91,file='profile_h2o_ice',status='old',
     773     &           form='formatted',iostat=ierr)
     774                 if (ierr.eq.0) then
     775                    read(91,*) qsurf(iq)
     776                    do ilayer=1,nlayer
     777                       read(91,*) q(ilayer,iq)
     778                    enddo
     779                 else
     780                    write(*,*) "No profile_h2o_ice file!"
     781                 endif
     782                 close(91)
     783              endif ! of if (txt.eq."h2o_ice")
     784
     785              !_vap
     786              if((txt .ne. 'h2o_vap') .and.
     787     &                       (index(txt,'_vap'   ) .ne. 0))   then
     788                    q(:,iq)=0. !kg/kg of atmosphere
     789                    qsurf(iq) = 0. !kg/kg of atmosphere
     790                    ! Look for a "profile_...._vap" input file
     791                    tracer_profile_file_name=""
     792                    tracer_profile_file_name='profile_'//txt
     793                    open(91,file=tracer_profile_file_name,status='old',
     794     &              form="formatted",iostat=ierr)
     795                    if (ierr .eq. 0) then
     796                          read(91,*)qsurf(iq)
     797                          do ilayer=1,nlayer
     798                                read(91,*)q(ilayer,iq)
     799                          enddo
     800                    else
     801                          write(*,*) "No initial profile "
     802                          write(*,*) " for this tracer :"
     803                          write(*,*) txt
     804                    endif
     805                    close(91)
     806              endif ! (txt .eq. "_vap")
     807              !_ice
     808              if((txt.ne."h2o_ice") .and.
     809     &                        (index(txt,'_ice'   ) /= 0)) then
     810                    q(:,iq)=0. !kg/kg of atmosphere
     811                    qsurf(iq) = 0. !kg/kg of atmosphere
     812              endif ! we only initialize the solid at 0
     813            endif ! restart
     814           enddo ! of do iq=1,nq
     815       
    720816      endif ! of tracer
    721817
     
    739835      w(1:nlayer)=0
    740836
    741 c     Initialisation des vents  au premier pas de temps
    742       DO ilayer=1,nlayer
    743          u(ilayer)=gru
    744          v(ilayer)=grv
    745       ENDDO
     837      if (restart) then
     838            ierr=NF90_INQ_VARID(nid_restart1D,'u',uid)
     839            if (ierr==NF90_NOERR) then
     840              ierr=NF90_GET_VAR(nid_restart1D,uid,u,
     841     &                          count=(/1,nlayer,1,1/))
     842              if (ierr/=NF90_NOERR) then
     843                PRINT*, 'read restart 1D: Failed loading u'
     844                write(*,*)trim(nf90_strerror(ierr))
     845                CALL abort_physic("readstart1D",
     846     &                            "Failed to read variable",1)
     847              endif
     848            endif
     849            ierr=NF90_INQ_VARID(nid_restart1D,'v',vid)
     850            if (ierr==NF90_NOERR) then
     851              ierr=NF90_GET_VAR(nid_restart1D,vid,v,
     852     &                          count=(/1,nlayer,1,1/))
     853              if (ierr/=NF90_NOERR) then
     854                PRINT*, 'read restart 1D: Failed loading v'
     855                write(*,*)trim(nf90_strerror(ierr))
     856                CALL abort_physic("readstart1D",
     857     &                            "Failed to read variable",1)
     858              endif
     859            endif
     860      else ! restart
     861
     862c       Initialisation des vents  au premier pas de temps
     863        DO ilayer=1,nlayer
     864           u(ilayer)=gru
     865           v(ilayer)=grv
     866        ENDDO
     867
     868      endif ! restart
    746869
    747870c     energie cinetique turbulente
     
    859982!      endif
    860983
     984
    861985c  profil de temperature au premier appel
    862986c  --------------------------------------
    863987      pks=psurf**rcp
    864988
     989      if (restart) then
     990            ! read temp
     991            ierr=NF90_IN Q_VARID(nid_restart1D,'temp',tempid)
     992            if (ierr==NF90_NOERR) then
     993              ierr=NF90_GET_VAR(nid_restart1D,tempid,temp,
     994     &                          count=(/1,nlayer,1,1/))
     995              if (ierr/=NF90_NOERR) then
     996                PRINT*, 'read restart 1D: Failed loading temp'
     997                CALL abort_physic("readstart1D",
     998     &                            "Failed to read variable",1)
     999              endif
     1000            endif
     1001            ! read tsurf
     1002            ierr=NF90_INQ_VARID(nid_restartfi,'tsurf',tsurfid)
     1003            if (ierr==NF90_NOERR) then
     1004              ierr=NF90_GET_VAR(nid_restartfi,tsurfid,tsurf)
     1005              if (ierr/=NF90_NOERR) then
     1006                PRINT*, 'read restartfi: Failed loading tsurf'
     1007                CALL abort_physic("readstartfi",
     1008     &                            "Failed to read variable",1)
     1009              endif
     1010            endif
     1011      else ! restart
     1012
    8651013c altitude en km dans profile: on divise zlay par 1000
    866       tmp1(0)=0.E+0
    867       DO ilayer=1,nlayer
    868         tmp1(ilayer)=zlay(ilayer)/1000.E+0
    869       ENDDO
    870       call profile(nlayer+1,tmp1,tmp2)
    871 
    872       tsurf(1)=tmp2(0)
    873       DO ilayer=1,nlayer
    874         temp(ilayer)=tmp2(ilayer)
    875       ENDDO
    876       print*,"check"
    877       PRINT*,"INPUT SURFACE TEMPERATURE",tsurf(1)
    878       PRINT*,"INPUT TEMPERATURE PROFILE",temp
     1014        tmp1(0)=0.E+0
     1015        DO ilayer=1,nlayer
     1016          tmp1(ilayer)=zlay(ilayer)/1000.E+0
     1017        ENDDO
     1018        call profile(nlayer+1,tmp1,tmp2)
     1019
     1020        tsurf(1)=tmp2(0)
     1021        DO ilayer=1,nlayer
     1022          temp(ilayer)=tmp2(ilayer)
     1023        ENDDO
     1024        print*,"check"
     1025        PRINT*,"INPUT SURFACE TEMPERATURE",tsurf(1)
     1026        PRINT*,"INPUT TEMPERATURE PROFILE",temp
     1027
     1028      endif ! restart
    8791029
    8801030c  Initialisation albedo / inertie du sol
     
    9371087! -----------------
    9381088#ifndef MESOSCALE
    939       if(tracer.and.photochem) then
     1089      if(tracer.and.photochem.and. .not.restart) then
     1090           print*, "Calling inichim_1D"
    9401091           call initracer(1,nq)
    9411092           allocate(nametmp(nq))
     
    9471098#endif
    9481099
     1100      if (restart) then
     1101        ierr = NF90_CLOSE(nid_restart1D)
     1102        if (ierr/=NF90_NOERR) then
     1103            PRINT*, 'read restart1D: Failed closing restart1D.nc'
     1104            CALL abort_physic("readstart1D",
     1105     &                        "Failed closing file",1)
     1106          endif
     1107        ierr = NF90_CLOSE(nid_restartfi)
     1108        if (ierr/=NF90_NOERR) then
     1109            PRINT*, 'read restartfi: Failed closing restartfi.nc'
     1110            CALL abort_physic("readstartfi",
     1111     &                        "Failed closing file",1)
     1112          endif
     1113      endif
    9491114
    9501115c  Write a "startfi" file
     
    9531118c  It is needed to transfert physics variables to "physiq"...
    9541119
    955       call physdem0("startfi.nc",longitude,latitude,nsoilmx,1,llm,nq,
    956      &              dtphys,real(day0),time,cell_area,
    957      &              albedodat,inertiedat,zmea,zstd,zsig,zgam,zthe)
    958       call physdem1("startfi.nc",nsoilmx,1,llm,nq,
    959      &                dtphys,time,
    960      &                tsurf,tsoil,emis,albedo,q2,qsurf,
    961      &                cloudfrac,totcloudfrac,hice,
    962      &                rnat,pctsrf_sic,tslab,tsea_ice,tice,sea_ice)
    963 
     1120      if (.not. restart) then
     1121        call physdem0("startfi.nc",longitude,latitude,nsoilmx,1,llm,nq,
     1122     &                dtphys,real(day0),time,cell_area,
     1123     &                albedodat,inertiedat,zmea,zstd,zsig,zgam,zthe)
     1124        call physdem1("startfi.nc",nsoilmx,1,llm,nq,
     1125     &                  dtphys,time,
     1126     &                  tsurf,tsoil,emis,albedo,q2,qsurf,
     1127     &                  cloudfrac,totcloudfrac,hice,
     1128     &                  rnat,pctsrf_sic,tslab,tsea_ice,tice,sea_ice)
     1129      endif
    9641130c=======================================================================
    9651131c  BOUCLE TEMPORELLE DU MODELE 1D
     
    10981264      endif
    10991265
     1266c     Produce the restart1D.nc file (MM)
     1267      if (lastcall) then
     1268        call writerestart1D('restart1D.nc',nlayer,nsoil,day,time,psurf,
     1269     &                                     temp,tsoil,u,v,nq,q)   
     1270      endif
    11001271
    11011272      ENDDO   ! fin de la boucle temporelle
  • trunk/LMDZ.GENERIC/libf/phystd/iostart.F90

    r3552 r3562  
    11401140  END SUBROUTINE put_var_c1
    11411141
     1142!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     1143
     1144  SUBROUTINE create_restart1D(filename,nid_restart)
     1145    USE netcdf, only: NF90_CREATE, NF90_CLOBBER, NF90_64BIT_OFFSET, &
     1146                      NF90_NOERR, nf90_strerror, &
     1147                      NF90_PUT_ATT, NF90_GLOBAL, NF90_DEF_DIM, &
     1148                      NF90_UNLIMITED, NF90_ENDDEF
     1149    USE mod_phys_lmdz_para, only: is_master
     1150    USE mod_grid_phy_lmdz, only: klon_glo
     1151    USE dimphy, only: klev, klevp1
     1152    USE tracer_h, only: nqtot
     1153    USE comsoil_h, only: nsoilmx
     1154  !  USE slab_ice_h, only: noceanmx
     1155    USE ocean_slab_mod, ONLY: nslay
     1156 
     1157    IMPLICIT NONE
     1158      CHARACTER(LEN=*),INTENT(IN) :: filename
     1159      INTEGER,INTENT(INOUT)       :: nid_restart
     1160      INTEGER                     :: ierr
     1161     
     1162      IF (is_master) THEN
     1163       
     1164          ierr=NF90_CREATE(filename,IOR(NF90_CLOBBER,NF90_64BIT_OFFSET), &
     1165                            nid_restart)
     1166          IF (ierr/=NF90_NOERR) THEN
     1167            write(*,*)'create_restart1D: problem creating file '//trim(filename)
     1168            write(*,*)trim(nf90_strerror(ierr))
     1169            CALL abort_physic("create_restart1D","Failed creating file",1)
     1170          ENDIF
     1171 
     1172        ierr=NF90_PUT_ATT(nid_restart,NF90_GLOBAL,"title",&
     1173                          "Physics start file")
     1174        IF (ierr/=NF90_NOERR) THEN
     1175          write(*,*)'create_restart1D: problem writing title '
     1176          write(*,*)trim(nf90_strerror(ierr))
     1177        ENDIF
     1178       
     1179        ierr=NF90_DEF_DIM(nid_restart,"physical_points",klon_glo,idim2)
     1180        IF (ierr/=NF90_NOERR) THEN
     1181          write(*,*)'create_restart1D: problem defining physical_points dimension '
     1182          write(*,*)trim(nf90_strerror(ierr))
     1183          CALL abort_physic("create_restart1D","Failed defining physical_points",1)
     1184        ENDIF
     1185 
     1186        ierr=NF90_DEF_DIM(nid_restart,"nlayer",klev,idim6)
     1187        IF (ierr/=NF90_NOERR) THEN
     1188          write(*,*)'create_restart1D: problem defining nlayer dimension '
     1189          write(*,*)trim(nf90_strerror(ierr))
     1190          CALL abort_physic("create_restart1D","Failed defining nlayer",1)
     1191        ENDIF
     1192 
     1193        ierr=NF90_ENDDEF(nid_restart)
     1194        IF (ierr/=NF90_NOERR) THEN
     1195          write(*,*)'create_restart1D: problem ending definition mode '
     1196          write(*,*)trim(nf90_strerror(ierr))
     1197          CALL abort_physic("create_restart1D","Failed ending definition mode",1)
     1198        ENDIF
     1199      ENDIF
     1200 
     1201    END SUBROUTINE create_restart1D
     1202
    11421203END MODULE iostart
  • trunk/LMDZ.GENERIC/libf/phystd/physiq_mod.F90

    r3522 r3562  
    792792
    793793#ifndef MESOSCALE
    794          if (ngrid.ne.1) then ! Note : no need to create a restart file in 1d.
     794         !if (ngrid.ne.1) then ! Note : no need to create a restart file in 1d.
    795795            call physdem0("restartfi.nc",longitude,latitude,nsoilmx,ngrid,nlayer,nq, &
    796796                         ptimestep,pday+nday,time_phys,cell_area,          &
    797797                         albedo_bareground,inertiedat,zmea,zstd,zsig,zgam,zthe)
    798          endif
     798         !endif
    799799
    800800#endif
     
    23972397#ifndef MESOSCALE
    23982398
    2399          if (ngrid.ne.1) then
     2399         !if (ngrid.ne.1) then
    24002400            write(*,*)'PHYSIQ: for physdem ztime_fin =',ztime_fin
    24012401
     
    24112411                          cloudfrac,totcloudfrac,hice,            &
    24122412                          rnat,pctsrf_sic,tslab,tsea_ice,tice,sea_ice)
    2413          endif
     2413         !endif
    24142414#endif
    24152415         if(ok_slab_ocean) then
Note: See TracChangeset for help on using the changeset viewer.