Ignore:
Timestamp:
12/15/14 17:04:28 (9 years ago)
Author:
ymipsl
Message:
  • implement splitting of XIOS file for lmdz physics
  • Termination is done properly in parallel by calling MPI_ABORT instead of abort or stop

YM

Location:
codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf
Files:
1 added
4 deleted
45 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/dyn3dpar/initialize_physics.F90

    r253 r313  
    11SUBROUTINE initialize_unstructured_physics(nbp, nlayer, communicator, nb_proc, distrib, & 
    2                                            punjours, pdayref,ptimestep,                  & 
     2                                           punjours, pdayref,time0,ptimestep,                  & 
    33                                           nb_vertex, lat, lon, area, bounds_lon, bounds_lat, & 
    44                                           prad,pg,pr,pcpp, preff,ap,bp ) 
     
    3737    REAL,INTENT(in)    :: bounds_lat(nbp,nb_vertex) ! latitude boundaries of cell 
    3838    INTEGER,INTENT(in) :: pdayref ! reference day of for the simulation 
     39    INTEGER,INTENT(in) :: time0 ! initialtime (s) 
    3940    REAL,INTENT(in)    :: ptimestep ! physics time step (s) 
    4041    REAL,INTENT(in)    :: preff      ! reference surface pressure (Pa) 
     
    7980                rlatd,rlond,airephy,prad,pg,pr,pcpp) 
    8081                 
    81     CALL initialize_xios_output         
     82    CALL initialize_xios_output(time0)         
    8283!$OMP END PARALLEL 
    8384 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/aeropacity.F90

    r298 r313  
    208208                  end do 
    209209 
    210                   call abort 
     210                  call abort_physiq 
    211211               endif 
    212212 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/ave_stelspec.F90

    r227 r313  
    8888            file_id='/stellar_spectra/gj644.txt' 
    8989            print*,'Find out tstellar before using this star!' 
    90             call abort 
     90            call abort_physiq 
    9191            file_id_lam='/stellar_spectra/lam.txt' 
    9292            Nfine=5000 
     
    113113           Case Default 
    114114            print*,'Error: unknown star type chosen' 
    115             call abort 
     115            call abort_physiq 
    116116         End Select 
    117117 
     
    128128           write(*,*)' datadir = /absolute/path/to/datagcm' 
    129129           write(*,*)' Also check that there is a ',trim(file_id_lam),' there.' 
    130            call abort 
     130           call abort_physiq 
    131131         else 
    132132           do ifine=1,Nfine 
     
    147147           write(*,*)' datadir = /absolute/path/to/datagcm' 
    148148           write(*,*)' Also check that there is a ',trim(file_id),' there.' 
    149            call abort 
     149           call abort_physiq 
    150150         else 
    151151           do ifine=1,Nfine 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/calc_cpp_mugaz.F90

    r298 r313  
    7979            else 
    8080               print*,'Error in calc_cpp_mugaz: Gas species not recognised!' 
    81                call abort 
     81               call abort_physiq 
    8282            endif 
    8383         endif 
     
    102102            print*,'    Either adjust cpp / mugaz via newstart to calculated values,' 
    103103            print*,'    or set check_cpp_match to .false. in callphys.def.' 
    104             stop 
     104            CALL abort_physiq 
    105105         else 
    106106            if (is_master) print*,'--> OK. Settings match composition.' 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/callcorrk.F90

    r298 r313  
    211211         if(naerkind.gt.4)then 
    212212            print*,'Code not general enough to deal with naerkind > 4 yet.' 
    213             call abort 
     213            call abort_physiq 
    214214         endif 
    215215         call su_aer_radii(ngrid,nlayer,reffrad,nueffrad) 
     
    235235         if((igcm_h2o_vap.eq.0) .and. varactive)then 
    236236            print*,'varactive in callcorrk but no h2o_vap tracer.' 
    237             stop 
     237            CALL abort_physiq 
    238238         endif 
    239239 
     
    250250           if (global1d.and.diurnal) then 
    251251            print*,'if global1d is true, diurnal must be set to false' 
    252             stop 
     252            CALL abort_physiq 
    253253           endif 
    254254 
     
    407407                        print*,'Serious problems with qsvaer values'  
    408408                        print*,'in callcorrk' 
    409                         call abort 
     409                        call abort_physiq 
    410410                     endif 
    411411                     if(qsvaer(k,nw,iaer).gt.qxvaer(k,nw,iaer))then 
     
    418418                        print*,'Serious problems with qsiaer values' 
    419419                        print*,'in callcorrk' 
    420                         call abort 
     420                        call abort_physiq 
    421421                     endif 
    422422                     if(qsiaer(k,nw,iaer).gt.qxiaer(k,nw,iaer))then 
     
    457457         print*,'For open lower boundary in callcorrk must' 
    458458         print*,'have surface albedo set to zero!' 
    459          call abort 
     459         call abort_physiq 
    460460      endif 
    461461 
     
    556556            if(nq.gt.1)then 
    557557               print*,'Need 1 tracer only to run kcm1d.e'  
    558                stop 
     558               CALL abort_physiq 
    559559            endif 
    560560            do l=1,nlayer 
     
    639639         print*,'Minimum pressure is outside the radiative' 
    640640         print*,'transfer kmatrix bounds, exiting.' 
    641          call abort 
     641         call abort_physiq 
    642642      elseif(plevrad(L_LEVELS).gt.pgasmax)then 
    643643         print*,'Maximum pressure is outside the radiative' 
    644644         print*,'transfer kmatrix bounds, exiting.' 
    645          call abort 
     645         call abort_physiq 
    646646      endif 
    647647 
     
    654654            print*,"tgasmin=",tgasmin 
    655655            if (strictboundcorrk) then 
    656               call abort 
     656              call abort_physiq 
    657657            else 
    658658              print*,'***********************************************' 
     
    669669            print*,"tgasmax=",tgasmax 
    670670            if (strictboundcorrk) then 
    671               call abort 
     671              call abort_physiq 
    672672            else 
    673673              print*,'***********************************************' 
     
    687687            print*,"tgasmin=",tgasmin 
    688688            if (strictboundcorrk) then 
    689               call abort 
     689              call abort_physiq 
    690690            else 
    691691              print*,'***********************************************' 
     
    702702            print*,"tgasmax=",tgasmax 
    703703            if (strictboundcorrk) then 
    704               call abort 
     704              call abort_physiq 
    705705            else 
    706706              print*,'***********************************************' 
     
    787787            print*,'temp=   ',pt(ig,:) 
    788788            print*,'pplay=  ',pplay(ig,:) 
    789             call abort 
     789            call abort_physiq 
    790790         endif 
    791791 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/callsedim.F

    r227 r313  
    8181            write(*,*) "callsedim error: water=.true.", 
    8282     &                 " but igcm_h2o_ice=0" 
    83           stop 
     83          CALL abort_physiq 
    8484          endif 
    8585          if (iaero_h2o.eq.0) then 
    8686            write(*,*) "callsedim error: water=.true.", 
    8787     &                 " but iaero_ho2=0" 
    88           stop 
     88          CALL abort_physiq 
    8989          endif 
    9090        endif 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/condense_cloud.F90

    r227 r313  
    175175           print*,'In condens_cloud but no CO2 ice tracer, exiting.' 
    176176           print*,'Still need generalisation to arbitrary species!' 
    177            stop 
     177           CALL abort_physiq 
    178178        endif 
    179179 
     
    401401            write(116,*) 0.0, pplev(1,1), 0.0, 0.0 
    402402            close(116) 
    403             call abort 
     403            call abort_physiq 
    404404         endif 
    405405 
     
    448448               PRINT*,'Ps = ',pplev(ig,1) 
    449449               PRINT*,'d Ps = ',pdpsrf(ig) 
    450                STOP 
     450               CALL abort_physiq 
    451451            ENDIF 
    452452         END IF 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/convadj.F

    r227 r313  
    9797             if (noms(iq).eq."co2") then 
    9898                print*,'dont go there' 
    99                 stop 
     99                CALL abort_physiq 
    100100                ico2=iq 
    101101                m_co2 = 44.01E-3  ! CO2 molecular mass (kg/mol)    
     
    297297                 zalpha=1. 
    298298              ELSE 
    299 !                IF(zalpha.LT.0.) STOP 
     299!                IF(zalpha.LT.0.) CALL abort_physiq 
    300300                 IF(zalpha.LT.1.e-4) zalpha=1.e-4 
    301301              ENDIF 
     
    381381            print*,'jadrs=',jadrs 
    382382 
    383             call abort 
     383            call abort_physiq 
    384384         endif 
    385385!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/cp_neutral.F90

    r222 r313  
    2222  else 
    2323     print*,'Gas not recognised in cp_neutral!' 
    24      call abort 
     24     call abort_physiq 
    2525  endif 
    2626 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/datareadnc.F

    r222 r313  
    118118        write(*,*)' can be obtained online on:' 
    119119        write(*,*)' http://www.lmd.jussieu.fr/~forget/datagcm/datafile' 
    120         STOP 
     120        CALL abort_physiq 
    121121      ENDIF 
    122122 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/def_var.F90

    r222 r313  
    3939   write(*,*) "def_var: Failed defining variable "//trim(name) 
    4040   write(*,*) NF_STRERROR(ierr) 
    41    stop "" 
     41   CALL abort_physiq  
    4242endif 
    4343 
     
    4848   write(*,*) "def_var: Failed writing title attribute for "//trim(name) 
    4949   write(*,*) NF_STRERROR(ierr) 
    50    stop "" 
     50   CALL abort_physiq  
    5151endif 
    5252 
     
    5656   write(*,*) "def_var: Failed writing units attribute for "//trim(name) 
    5757   write(*,*) NF_STRERROR(ierr) 
    58    stop "" 
     58   CALL abort_physiq  
    5959endif 
    6060 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/gfluxi.F

    r265 r313  
    6262  
    6363 
    64       IF (NLL .GT. NLP) STOP 'PARAMETER NL TOO SMALL IN GFLUXI' 
    65  
     64      IF (NLL .GT. NLP) THEN 
     65       PRINT*, 'PARAMETER NL TOO SMALL IN GFLUXI' 
     66       CALL abort_physiq 
     67      ENDIF 
     68       
    6669      NLAYER = L_NLAYRAD 
    6770 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/gradients_kcm.F90

    r222 r313  
    4343     if(ngasmx.eq.1)then 
    4444        print*,'Cannot have moist adiabat with one gas...' 
    45         stop 
     45        CALL abort_physiq 
    4646     endif 
    4747 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/hydrol.F90

    r227 r313  
    151151            print*,'How are we supposed to average the ocean' 
    152152            print*,'temperature, when there are no oceans?' 
    153             call abort 
     153            call abort_physiq 
    154154         endif 
    155155 
     
    157157            print*,'You have enabled runoff, but you have no oceans.' 
    158158            print*,'Where did you think the water was going to go?' 
    159             call abort 
     159            call abort_physiq 
    160160         endif 
    161161          
     
    315315            print*,'Surface type not recognised in hydrol.F!' 
    316316            print*,'Exiting...' 
    317             call abort 
     317            call abort_physiq 
    318318 
    319319         endif 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/iniaerosol.F

    r298 r313  
    7171          print*, 'or change options in callphys.def' 
    7272          print*, 'Abort in iniaerosol.F' 
    73           call abort 
     73          call abort_physiq 
    7474      endif 
    7575 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/inifis.F

    r310 r313  
    215215           if (is_master) print*,'If diurnal=true, we should turn off', 
    216216     &          ' tlocked.' 
    217            stop 
     217           CALL abort_physiq 
    218218         endif 
    219219 
     
    306306            if (is_master) print*,'We need a CO2 ice tracer to', 
    307307     &          ' condense CO2' 
    308             call abort 
     308            call abort_physiq 
    309309         endif  
    310310  
     
    393393         if (kastprof.and.(ngrid.gt.1)) then 
    394394           if (is_master) print*,'kastprof can only be used in 1D!' 
    395            call abort 
     395           call abort_physiq 
    396396         endif 
    397397 
     
    411411           if (is_master) print*,'nosurf not compatible with soil', 
    412412     &          ' scheme! ... got to make a choice!' 
    413            call abort 
     413           call abort_physiq 
    414414         endif 
    415415 
     
    430430           if (is_master) print*,'newtonian not compatible with ', 
    431431     &          'correlated-k!' 
    432            call abort 
     432           call abort_physiq 
    433433         endif 
    434434         if (newtonian.and.calladj) then 
    435435           if (is_master) print*,'newtonian not compatible with ', 
    436436     &          'adjustment!' 
    437            call abort 
     437           call abort_physiq 
    438438         endif 
    439439         if (newtonian.and.calldifv) then 
    440440           if (is_master) print*,'newtonian not compatible with a ', 
    441441     &          'boundary layer!' 
    442            call abort 
     442           call abort_physiq 
    443443         endif 
    444444 
     
    452452         if (testradtimes.and.(ngrid.gt.1)) then 
    453453           if (is_master) print*,'testradtimes can only be used in 1D!' 
    454            call abort 
     454           call abort_physiq 
    455455         endif 
    456456 
     
    624624         if (varactive.and.varfixed) then 
    625625           if (is_master) print*,'if varactive, varfixed must be OFF!' 
    626            stop 
     626           CALL abort_physiq 
    627627         endif 
    628628 
     
    642642           if (is_master) print*,'if water is ON, tracer must be ', 
    643643     &          'ON too!' 
    644            stop 
     644           CALL abort_physiq 
    645645         endif 
    646646 
     
    655655           if (is_master) print*,'if watercond is used, water should ', 
    656656     &          'be used too' 
    657            stop 
     657           CALL abort_physiq 
    658658         endif 
    659659 
     
    706706               if (is_master) PRINT *, "mugaz must be set if ', 
    707707     &          'force_cpp = T" 
    708                STOP 
     708               CALL abort_physiq 
    709709           ELSE 
    710710               if (is_master) write(*,*) "inifis: mugaz=",mugaz 
     
    722722               if (is_master) PRINT *, "cpp must be set if ', 
    723723     &          'force_cpp = T" 
    724                STOP 
     724               CALL abort_physiq 
    725725           ELSE 
    726726               if (is_master) write(*,*) "inifis: cpp=",cpp 
     
    739739         if (is_master) write(*,*) 'Cannot read file callphys.def.", 
    740740     &          " Is it here ?' 
    741          stop 
     741         CALL abort_physiq 
    742742      ENDIF 
    743743 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/inistats.F

    r222 r313  
    2727      nsteppd=nint(daysec/dtphys) 
    2828      write (*,*) 'nsteppd=',nsteppd 
    29       if (abs(float(nsteppd)-daysec/dtphys).gt.1.e-8*daysec) 
    30      &   stop'Dans Instat:  1jour .ne. n pas physiques' 
     29      if (abs(float(nsteppd)-daysec/dtphys).gt.1.e-8*daysec) THEN  
     30        PRINT *,'Dans Instat:  1jour .ne. n pas physiques' 
     31        CALL abort_physiq 
     32      endif 
    3133 
    32       if(mod(nsteppd,istime).ne.0) 
    33      &   stop'Dans Instat:  1jour .ne. n*istime pas physiques' 
     34      if(mod(nsteppd,istime).ne.0) THEN 
     35        PRINT*,'Dans Instat:  1jour .ne. n*istime pas physiques' 
     36        CALL abort_physiq 
     37      endif         
    3438 
    3539      istats=nsteppd/istime 
     
    5054      if (ierr.ne.NF_NOERR) then 
    5155         write (*,*) NF_STRERROR(ierr) 
    52          stop "" 
     56         CALL abort_physiq 
    5357      endif 
    5458 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/interpolateH2H2.F90

    r298 r313  
    6161         print*,'really want to run simulations with hydrogen at T > 400 K, contact' 
    6262         print*,'Robin Wordsworth [rwordsworth@uchicago.edu].' 
    63          stop 
     63         CALL abort_physiq 
    6464      endif 
    6565 
     
    8282           write(*,*) 'datadir = /absolute/path/to/datagcm' 
    8383           write(*,*) 'Also check that the continuum data continuum_data/H2-H2_norm_2011.cia is there.' 
    84            call abort 
     84           call abort_physiq 
    8585         else 
    8686 
     
    9292                  print*,'is ',nres,', which does not match nS.' 
    9393                  print*,'Please adjust nS value in interpolateH2H2.F90' 
    94                   stop 
     94                  CALL abort_physiq 
    9595               endif 
    9696               temp_arr(iT)=Ttemp 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/iostart.F90

    r270 r313  
    5757        write(*,*)'open_startphy: problem opening file '//trim(filename) 
    5858        write(*,*)trim(nf90_strerror(ierr)) 
    59         !CALL ABORT 
     59        !CALL abort_physiq 
    6060        found=.false. 
    6161      ELSE 
     
    125125                  //trim(field_name) 
    126126        write(*,*)trim(nf90_strerror(ierr)) 
    127         CALL ABORT 
     127        CALL abort_physiq 
    128128      ENDIF 
    129129    ENDIF 
     
    176176                  //trim(field_name) 
    177177        write(*,*)trim(nf90_strerror(ierr)) 
    178         CALL ABORT 
     178        CALL abort_physiq 
    179179      ENDIF 
    180180    ENDIF 
     
    315315      IF (.NOT. tmp_found) THEN 
    316316        PRINT*, 'get_field_rgen: Field <'//field_name//'> not found' 
    317         CALL abort 
     317        CALL abort_physiq 
    318318      ENDIF 
    319319    ENDIF 
     
    335335!              IF (ierr/=NF90_NOERR) THEN 
    336336!                 PRINT*, 'phyetat0: Lecture echouee aussi en 2D pour <'//field_name//'>' 
    337 !                 CALL abort 
     337!                 CALL abort_physiq 
    338338!              ELSE 
    339339!                 PRINT*, 'phyetat0: La variable <'//field_name//'> lu sur surface seulement'!, selon ancien format, le reste mis a zero' 
    340340!              END IF 
    341341!           ELSE 
    342               CALL abort 
     342              CALL abort_physiq 
    343343!           ENDIF 
    344344         ENDIF 
     
    435435        IF (ierr/=NF90_NOERR) THEN 
    436436          PRINT*, 'phyetat0: Failed loading <'//trim(var_name)//'>' 
    437           CALL abort 
     437          CALL abort_physiq 
    438438        ENDIF 
    439439        tmp_found=.TRUE. 
     
    455455      IF (.NOT. tmp_found) THEN 
    456456        PRINT*, 'phyetat0: Variable <'//trim(var_name)//'> not found' 
    457         CALL abort 
     457        CALL abort_physiq 
    458458      ENDIF 
    459459    ENDIF 
     
    490490          write(*,*)'open_restartphy: problem creating file '//trim(filename) 
    491491          write(*,*)trim(nf90_strerror(ierr)) 
    492           CALL ABORT 
     492          CALL abort_physiq 
    493493        ENDIF 
    494494        already_created=.true. 
     
    499499          write(*,*)'open_restartphy: problem opening file '//trim(filename) 
    500500          write(*,*)trim(nf90_strerror(ierr)) 
    501           CALL ABORT 
     501          CALL abort_physiq 
    502502        ENDIF 
    503503        return 
     
    515515        write(*,*)'open_restartphy: problem defining index dimension ' 
    516516        write(*,*)trim(nf90_strerror(ierr)) 
    517         CALL ABORT 
     517        CALL abort_physiq 
    518518      ENDIF 
    519519       
     
    522522        write(*,*)'open_restartphy: problem defining physical_points dimension ' 
    523523        write(*,*)trim(nf90_strerror(ierr)) 
    524         CALL ABORT 
     524        CALL abort_physiq 
    525525      ENDIF 
    526526       
     
    529529        write(*,*)'open_restartphy: problem defining subsurface_layers dimension ' 
    530530        write(*,*)trim(nf90_strerror(ierr)) 
    531         CALL ABORT 
     531        CALL abort_physiq 
    532532      ENDIF 
    533533       
     
    536536        write(*,*)'open_restartphy: problem defining nlayer_plus_1 dimension ' 
    537537        write(*,*)trim(nf90_strerror(ierr)) 
    538         CALL ABORT 
     538        CALL abort_physiq 
    539539      ENDIF 
    540540       
     
    545545          write(*,*)'open_restartphy: problem defining number_of_advected_fields dimension ' 
    546546          write(*,*)trim(nf90_strerror(ierr)) 
    547           CALL ABORT 
     547          CALL abort_physiq 
    548548        ENDIF 
    549549      endif 
     
    553553        write(*,*)'open_restartphy: problem defining nlayer dimension ' 
    554554        write(*,*)trim(nf90_strerror(ierr)) 
    555         CALL ABORT 
     555        CALL abort_physiq 
    556556      ENDIF 
    557557       
     
    560560        write(*,*)'open_restartphy: problem defining Time dimension ' 
    561561        write(*,*)trim(nf90_strerror(ierr)) 
    562         CALL ABORT 
     562        CALL abort_physiq 
    563563      ENDIF 
    564564 
     
    567567        write(*,*)'open_restartphy: problem defining oceanic layer dimension ' 
    568568        write(*,*)trim(nf90_strerror(ierr)) 
    569         CALL ABORT 
     569        CALL abort_physiq 
    570570      ENDIF 
    571571 
     
    575575        write(*,*)'open_restartphy: problem ending definition mode ' 
    576576        write(*,*)trim(nf90_strerror(ierr)) 
    577         CALL ABORT 
     577        CALL abort_physiq 
    578578      ENDIF 
    579579    ENDIF 
     
    884884        PRINT *, "Error phyredem(put_field_rgen) : wrong dimension for ",trim(field_name) 
    885885        write(*,*) "  field_size =",field_size 
    886         CALL ABORT 
     886        CALL abort_physiq 
    887887      ENDIF 
    888888 
     
    891891        write(*,*) " Error phyredem(put_field_rgen) : failed writing ",trim(field_name) 
    892892        write(*,*)trim(nf90_strerror(ierr)) 
    893         call abort 
     893        call abort_physiq 
    894894      endif 
    895895 
     
    996996          write(*,*)'put_var_rgen: problem writing Time' 
    997997          write(*,*)trim(nf90_strerror(ierr)) 
    998           CALL ABORT 
     998          CALL abort_physiq 
    999999        ENDIF 
    10001000        return ! nothing left to do 
     
    10111011        PRINT *, "put_var_rgen error : wrong dimension" 
    10121012        write(*,*) "  var_size =",var_size 
    1013         CALL abort 
     1013        CALL abort_physiq 
    10141014 
    10151015      ENDIF ! of IF (var_size==length) THEN 
     
    10321032        write(*,*)'put_var_rgen: problem writing '//trim(var_name) 
    10331033        write(*,*)trim(nf90_strerror(ierr)) 
    1034         CALL ABORT 
     1034        CALL abort_physiq 
    10351035      ENDIF 
    10361036    ENDIF ! of IF (is_master) 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/kcm1d.F90

    r227 r313  
    117117     write(*,*) '   )' 
    118118     write(*,*) ' ... might as well stop here ...' 
    119      stop 
     119     CALL abort_physiq 
    120120  else 
    121121     close(90) 
     
    133133     write(*,*) 'Please remove the file and restart the run.' 
    134134     write(*,*) 'Runtime parameters are supposed to be in kcm1d.def' 
    135      stop 
     135     CALL abort_physiq 
    136136  else 
    137137     call system('touch run.def') 
     
    144144  if(.not.global1d)then 
    145145     print*,'Error, kcm1d must have global1d=.true. in kcm1d.def!' 
    146      stop 
     146     CALL abort_physiq 
    147147  end if 
    148148 
     
    200200     print*,"In 1D modeling, check_cpp_match is supposed to be F" 
    201201     print*,"Please correct callphys.def" 
    202      stop 
     202     CALL abort_physiq 
    203203  endif 
    204204 
     
    221221           write(*,*) "kcm1d: error reading number of tracers" 
    222222           write(*,*) "   (first line of traceur.def) " 
    223            stop 
     223           CALL abort_physiq 
    224224        endif 
    225225        nqtot=nq 
     
    235235           if (ierr.ne.0) then 
    236236              write(*,*) 'kcm1d: error reading tracer names...' 
    237               stop 
     237              CALL abort_physiq 
    238238           endif 
    239239        enddo !of do iq=1,nq 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/kcmprof_fn.F90

    r227 r313  
    9595        print*,'Must have Psat_max=0 if no variable species' 
    9696        psat_max=0.0 
    97         !stop 
     97        !CALL abort_physiq 
    9898     endif 
    9999     print*, 'Assuming pure atmosphere' 
     
    109109     m_v   = 16.04/1000. 
    110110     tcrit = 1.91d2 
    111      stop 
     111     CALL abort_physiq 
    112112  else 
    113113     print*,'Variable gas not recognised!' 
    114      call abort 
     114     call abort_physiq 
    115115  endif 
    116116 
     
    326326           if(ilay.eq.1)then 
    327327              print*,'Error in create_profils: Psurf here less than Psurf in RCM!' 
    328               call abort 
     328              call abort_physiq 
    329329           endif 
    330330 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/lect_start_archive.F

    r227 r313  
    2121c 
    2222c   Objet:     Lecture des variables d'un fichier "start_archive" 
    23 c              Plus besoin de régler ancienne valeurs grace 
     23c              Plus besoin de rï¿œgler ancienne valeurs grace 
    2424c              a l'allocation dynamique de memoire (Yann Wanherdrick) 
    2525c 
     
    341341      IF (ierr .NE. NF_NOERR) THEN 
    342342         PRINT*, "Lect_start_archive: champ <controle> est absent" 
    343          CALL abort 
     343         CALL abort_physiq 
    344344      ENDIF 
    345345#ifdef NC_DOUBLE 
     
    350350      IF (ierr .NE. NF_NOERR) THEN 
    351351         PRINT*, "lect_start_archive: Lecture echoue pour <controle>" 
    352          CALL abort 
     352         CALL abort_physiq 
    353353      ENDIF 
    354354c 
     
    362362      IF (ierr .NE. NF_NOERR) THEN 
    363363         PRINT*, "lect_start_archive: Le champ <rlonv> est absent" 
    364          CALL abort 
     364         CALL abort_physiq 
    365365      ENDIF 
    366366#ifdef NC_DOUBLE 
     
    371371      IF (ierr .NE. NF_NOERR) THEN 
    372372         PRINT*, "lect_start_archive: Lecture echouee pour <rlonv>" 
    373          CALL abort 
     373         CALL abort_physiq 
    374374      ENDIF 
    375375c 
     
    377377      IF (ierr .NE. NF_NOERR) THEN 
    378378         PRINT*, "lect_start_archive: Le champ <rlatu> est absent" 
    379          CALL abort 
     379         CALL abort_physiq 
    380380      ENDIF  
    381381#ifdef NC_DOUBLE 
     
    386386      IF (ierr .NE. NF_NOERR) THEN 
    387387         PRINT*, "lect_start_archive: Lecture echouee pour <rlatu>" 
    388          CALL abort 
     388         CALL abort_physiq 
    389389      ENDIF 
    390390c 
     
    392392      IF (ierr .NE. NF_NOERR) THEN 
    393393         PRINT*, "lect_start_archive: Le champ <rlonu> est absent" 
    394          CALL abort 
     394         CALL abort_physiq 
    395395      ENDIF 
    396396#ifdef NC_DOUBLE 
     
    401401      IF (ierr .NE. NF_NOERR) THEN 
    402402         PRINT*, "lect_start_archive: Lecture echouee pour <rlonu>" 
    403          CALL abort 
     403         CALL abort_physiq 
    404404      ENDIF 
    405405c 
     
    407407      IF (ierr .NE. NF_NOERR) THEN 
    408408         PRINT*, "lect_start_archive: Le champ <rlatv> est absent" 
    409          CALL abort 
     409         CALL abort_physiq 
    410410      ENDIF 
    411411#ifdef NC_DOUBLE 
     
    416416      IF (ierr .NE. NF_NOERR) THEN 
    417417         PRINT*, "lect_start_archive: Lecture echouee pour <rlatv>" 
    418          CALL abort 
     418         CALL abort_physiq 
    419419      ENDIF 
    420420c 
     
    447447         IF (ierr .NE. NF_NOERR) THEN 
    448448            PRINT*, "Nothing to do..." 
    449             CALL abort 
     449            CALL abort_physiq 
    450450         ENDIF 
    451451      ENDIF 
     
    457457      IF (ierr .NE. NF_NOERR) THEN 
    458458         PRINT*, "lect_start_archive: Lecture echouee pour <bps>" 
    459          CALL abort 
     459         CALL abort_physiq 
    460460      END IF 
    461461 
     
    482482       if (ierr .NE. NF_NOERR) then 
    483483         PRINT*, "lect_start_archive: Failed reading <soildepth>" 
    484          CALL abort 
     484         CALL abort_physiq 
    485485       endif 
    486486 
     
    510510       if (ierr .NE. NF_NOERR) then 
    511511         PRINT*, "lect_start_archive: Failed reading <soildepth>" 
    512          CALL abort 
     512         CALL abort_physiq 
    513513       endif 
    514514      endif ! of if (depthinterpol) 
     
    535535       if (ierr .NE. NF_NOERR) then 
    536536         PRINT*, "lect_start_archive: Failed reading <inertiedat>" 
    537          CALL abort 
     537         CALL abort_physiq 
    538538       endif 
    539539      endif 
     
    546546      IF (ierr .NE. NF_NOERR) THEN 
    547547         PRINT*, "lect_start_archive: Le champ <phisinit> est absent" 
    548          CALL abort 
     548         CALL abort_physiq 
    549549      ENDIF 
    550550#ifdef NC_DOUBLE 
     
    555555      IF (ierr .NE. NF_NOERR) THEN 
    556556         PRINT*, "lect_start_archive: Lecture echouee pour <phisinit>" 
    557          CALL abort 
     557         CALL abort_physiq 
    558558      ENDIF 
    559559 
     
    575575         IF (ierr .NE. NF_NOERR) THEN 
    576576            PRINT*, "lect_start_archive: Le champ <Time> est absent" 
    577             CALL abort 
     577            CALL abort_physiq 
    578578         endif 
    579579      ENDIF 
     
    590590      IF (ierr .NE. NF_NOERR) THEN 
    591591         PRINT*, "lect_start_archive: Lecture echouee pour <Time>" 
    592          CALL abort 
     592         CALL abort_physiq 
    593593      ENDIF 
    594594c 
     
    649649!      IF (ierr .NE. NF_NOERR) THEN 
    650650!         PRINT*, "lect_start_archive: Le champ <co2ice> est absent" 
    651 !         CALL abort 
     651!         CALL abort_physiq 
    652652!      ENDIF 
    653653!#ifdef NC_DOUBLE 
     
    659659!         PRINT*, "lect_start_archive: Lecture echouee pour <co2ice>" 
    660660!         PRINT*, NF_STRERROR(ierr) 
    661 !         CALL abort 
     661!         CALL abort_physiq 
    662662!      ENDIF 
    663663c 
     
    665665      IF (ierr .NE. NF_NOERR) THEN 
    666666         PRINT*, "lect_start_archive: Le champ <emis> est absent" 
    667          CALL abort 
     667         CALL abort_physiq 
    668668      ENDIF 
    669669#ifdef NC_DOUBLE 
     
    674674      IF (ierr .NE. NF_NOERR) THEN 
    675675         PRINT*, "lect_start_archive: Lecture echouee pour <emis>" 
    676          CALL abort 
     676         CALL abort_physiq 
    677677      ENDIF 
    678678c 
     
    680680      IF (ierr .NE. NF_NOERR) THEN 
    681681         PRINT*, "lect_start_archive: Le champ <ps> est absent" 
    682          CALL abort 
     682         CALL abort_physiq 
    683683      ENDIF 
    684684#ifdef NC_DOUBLE 
     
    689689      IF (ierr .NE. NF_NOERR) THEN 
    690690         PRINT*, "lect_start_archive: Lecture echouee pour <ps>" 
    691          CALL abort 
     691         CALL abort_physiq 
    692692      ENDIF 
    693693c 
     
    695695      IF (ierr .NE. NF_NOERR) THEN 
    696696         PRINT*, "lect_start_archive: Le champ <tsurf> est absent" 
    697          CALL abort 
     697         CALL abort_physiq 
    698698      ENDIF 
    699699#ifdef NC_DOUBLE 
     
    704704      IF (ierr .NE. NF_NOERR) THEN 
    705705         PRINT*, "lect_start_archive: Lecture echouee pour <tsurf>" 
    706          CALL abort 
     706         CALL abort_physiq 
    707707      ENDIF 
    708708c 
     
    710710      IF (ierr .NE. NF_NOERR) THEN 
    711711         PRINT*, "lect_start_archive: Le champ <q2surf> est absent" 
    712          CALL abort 
     712         CALL abort_physiq 
    713713      ENDIF 
    714714#ifdef NC_DOUBLE 
     
    719719      IF (ierr .NE. NF_NOERR) THEN 
    720720         PRINT*, "lect_start_archive: Lecture echouee pour <q2surf>" 
    721          CALL abort 
     721         CALL abort_physiq 
    722722      ENDIF 
    723723c 
     
    833833 
    834834!          print*,'RDW has added hack to let me continue...' 
    835 !          CALL abort 
     835!          CALL abort_physiq 
    836836        ENDIF 
    837837#ifdef NC_DOUBLE 
     
    871871            PRINT*, "lect_start_archive: ", 
    872872     &              "Field <","Tg"//str2,"> not found" 
    873             CALL abort 
     873            CALL abort_physiq 
    874874         ENDIF 
    875875#ifdef NC_DOUBLE 
     
    883883            PRINT*, "lect_start_archive: ", 
    884884     &            "Failed reading <","Tg"//str2,">" 
    885             CALL abort 
     885            CALL abort_physiq 
    886886         ENDIF 
    887887c 
     
    897897       if (ierr.ne.NF_NOERR) then 
    898898        write(*,*)"lect_start_archive: Cannot find <tsoil>" 
    899         call abort 
     899        call abort_physiq 
    900900       else 
    901901#ifdef NC_DOUBLE 
     
    915915!       if (ierr.ne.NF_NOERR) then 
    916916!        write(*,*)"lect_start_archive: Cannot find <inertiedat>" 
    917 !       call abort 
     917!       call abort_physiq 
    918918!       else 
    919919!#ifdef NC_DOUBLE 
     
    936936      IF (ierr .NE. NF_NOERR) THEN 
    937937         PRINT*, "lect_start_archive: Le champ <temp> est absent" 
    938          CALL abort 
     938         CALL abort_physiq 
    939939      ENDIF 
    940940#ifdef NC_DOUBLE 
     
    945945      IF (ierr .NE. NF_NOERR) THEN 
    946946         PRINT*, "lect_start_archive: Lecture echouee pour <temp>" 
    947          CALL abort 
     947         CALL abort_physiq 
    948948      ENDIF 
    949949c 
     
    951951      IF (ierr .NE. NF_NOERR) THEN 
    952952         PRINT*, "lect_start_archive: Le champ <u> est absent" 
    953          CALL abort 
     953         CALL abort_physiq 
    954954      ENDIF 
    955955#ifdef NC_DOUBLE 
     
    960960      IF (ierr .NE. NF_NOERR) THEN 
    961961         PRINT*, "lect_start_archive: Lecture echouee pour <u>" 
    962          CALL abort 
     962         CALL abort_physiq 
    963963      ENDIF 
    964964c 
     
    966966      IF (ierr .NE. NF_NOERR) THEN 
    967967         PRINT*, "lect_start_archive: Le champ <v> est absent" 
    968          CALL abort 
     968         CALL abort_physiq 
    969969      ENDIF 
    970970#ifdef NC_DOUBLE 
     
    975975      IF (ierr .NE. NF_NOERR) THEN 
    976976         PRINT*, "lect_start_archive: Lecture echouee pour <v>" 
    977          CALL abort 
     977         CALL abort_physiq 
    978978      ENDIF 
    979979c 
     
    981981      IF (ierr .NE. NF_NOERR) THEN 
    982982         PRINT*, "lect_start_archive: Le champ <q2atm> est absent" 
    983          CALL abort 
     983         CALL abort_physiq 
    984984      ENDIF 
    985985#ifdef NC_DOUBLE 
     
    990990      IF (ierr .NE. NF_NOERR) THEN 
    991991         PRINT*, "lect_start_archive: Lecture echouee pour <q2atm>" 
    992          CALL abort 
     992         CALL abort_physiq 
    993993      ENDIF 
    994994c 
     
    10061006            PRINT*, "lect_start_archive: ", 
    10071007     &              " Tracer <",trim(txt),"> not found" 
    1008 !            CALL abort 
     1008!            CALL abort_physiq 
    10091009        ENDIF 
    10101010#ifdef NC_DOUBLE 
     
    12261226               !print*,'Problem in lect_start_archive interpolating' 
    12271227               !print*,'to new resolution!!' 
    1228                !call abort 
     1228               !call abort_physiq 
    12291229            !endif 
    12301230 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/mass_redistribution.F90

    r227 r313  
    176176         PRINT*,'Ps = ',pplev(ig,1) 
    177177         PRINT*,'d Ps = ',pdpsrfmr(ig)*ptimestep 
    178          STOP 
     178         CALL abort_physiq 
    179179        ENDIF 
    180180      enddo ! of DO ig=1,ngrid 
     
    379379                print*,q 
    380380                print*,qm 
    381                stop 
     381               CALL abort_physiq 
    382382             end if 
    383383          else      ! if(w(l+1).lt.0)  
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/mod_phys_lmdz_mpi_transfert.F90

    r245 r313  
    6060!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 
    6161 
    62 !! -- Les chaine de charactère -- !! 
     62!! -- Les chaine de charactï¿œre -- !! 
    6363 
    6464  SUBROUTINE bcast_mpi_c(var1) 
     
    13211321    if (ierr.ne.MPI_SUCCESS) then 
    13221322      write(*,*) "bcast_mpi error: ierr=",ierr 
    1323       stop 
     1323      CALL abort_physiq 
    13241324    endif 
    13251325#endif 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/newstart.F

    r227 r313  
    231231          write(6,*)' Problem opening file:',fichnom 
    232232          write(6,*)' ierr = ', ierr 
    233           CALL ABORT 
     233          CALL abort_physiq 
    234234        ENDIF 
    235235        tab0 = 50  
     
    247247          write(6,*)' Problem opening file:',fichnom 
    248248          write(6,*)' ierr = ', ierr 
    249           CALL ABORT 
     249          CALL abort_physiq 
    250250        ENDIF 
    251251  
     
    255255          write(6,*)' Problem opening file:',fichnom 
    256256          write(6,*)' ierr = ', ierr 
    257           CALL ABORT 
     257          CALL abort_physiq 
    258258        ENDIF 
    259259 
     
    10241024        if (igcm_h2o_vap.eq.0) then 
    10251025          write(*,*) "No water vapour tracer! Can't use this option" 
    1026           stop 
     1026          CALL abort_physiq 
    10271027        endif 
    10281028          DO l=1,llm 
     
    10441044           if (igcm_h2o_ice.eq.0) then 
    10451045             write(*,*) "No water ice tracer! Can't use this option" 
    1046              stop 
     1046             CALL abort_physiq 
    10471047           endif 
    10481048           do ig=1,ngridmx 
     
    10611061           if (igcm_h2o_ice.eq.0) then 
    10621062             write(*,*) "No water ice tracer! Can't use this option" 
    1063              stop 
     1063             CALL abort_physiq 
    10641064           endif 
    10651065 
     
    11031103           if (igcm_h2o_ice.eq.0) then 
    11041104              write(*,*) "No water ice tracer! Can't use this option" 
    1105               stop 
     1105              CALL abort_physiq 
    11061106           endif 
    11071107 
     
    11441144           if (igcm_h2o_ice.eq.0) then 
    11451145             write(*,*) "No water ice tracer! Can't use this option" 
    1146              stop 
     1146             CALL abort_physiq 
    11471147           endif 
    11481148          DO j=1,jjp1         
     
    11731173           if (igcm_h2o_ice.eq.0) then 
    11741174             write(*,*) "No water ice tracer! Can't use this option" 
    1175              stop 
     1175             CALL abort_physiq 
    11761176           endif 
    11771177          DO j=1,jjp1         
     
    12051205           if (igcm_h2o_ice.eq.0) then 
    12061206             write(*,*) "No water ice tracer! Can't use this option" 
    1207              stop 
     1207             CALL abort_physiq 
    12081208           endif 
    12091209          DO j=1,jjp1         
     
    12291229           if (igcm_h2o_ice.eq.0) then 
    12301230             write(*,*) "No water ice tracer! Can't use this option" 
    1231              stop 
     1231             CALL abort_physiq 
    12321232           endif 
    12331233          DO j=1,jjp1         
     
    12581258           if (igcm_h2o_ice.eq.0) then 
    12591259             write(*,*) "No water ice tracer! Can't use this option" 
    1260              stop 
     1260             CALL abort_physiq 
    12611261           endif 
    12621262          DO j=1,jjp1         
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/phyetat0.F90

    r227 r313  
    1616!====================================================================== 
    1717! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818 
    18 !  Adaptation à Mars : Yann Wanherdrick  
     18!  Adaptation ï¿œ Mars : Yann Wanherdrick  
    1919! Objet: Lecture de l etat initial pour la physique 
    2020!====================================================================== 
     
    113113!      IF (ierr.NE.NF_NOERR) THEN 
    114114!         PRINT*, 'phyetat0: Le champ <latitude> est absent' 
    115 !         CALL abort 
     115!         CALL abort_physiq 
    116116!      ENDIF 
    117117!#ifdef NC_DOUBLE 
     
    122122!      IF (ierr.NE.NF_NOERR) THEN 
    123123!         PRINT*, 'phyetat0: Lecture echouee pour <latitude>' 
    124 !         CALL abort 
     124!         CALL abort_physiq 
    125125!      ENDIF 
    126126!c 
     
    130130!      IF (ierr.NE.NF_NOERR) THEN 
    131131!         PRINT*, 'phyetat0: Le champ <longitude> est absent' 
    132 !         CALL abort 
     132!         CALL abort_physiq 
    133133!      ENDIF 
    134134!#ifdef NC_DOUBLE 
     
    139139!      IF (ierr.NE.NF_NOERR) THEN 
    140140!         PRINT*, 'phyetat0: Lecture echouee pour <longitude>' 
    141 !         CALL abort 
     141!         CALL abort_physiq 
    142142!      ENDIF 
    143143!c 
     
    147147!      IF (ierr.NE.NF_NOERR) THEN 
    148148!         PRINT*, 'phyetat0: Le champ <area> est absent' 
    149 !         CALL abort 
     149!         CALL abort_physiq 
    150150!      ENDIF 
    151151!#ifdef NC_DOUBLE 
     
    156156!      IF (ierr.NE.NF_NOERR) THEN 
    157157!         PRINT*, 'phyetat0: Lecture echouee pour <area>' 
    158 !         CALL abort 
     158!         CALL abort_physiq 
    159159!      ENDIF 
    160160!      xmin = 1.0E+20 
     
    168168if (.not.found) then 
    169169  write(*,*) "phyetat0: Failed loading <phisfi>" 
    170   call abort 
     170  call abort_physiq 
    171171else 
    172172  write(*,*) "phyetat0: surface geopotential <phisfi> range:", & 
     
    178178if (.not.found) then 
    179179  write(*,*) "phyetat0: Failed loading <albedodat>" 
    180   call abort 
     180  call abort_physiq 
    181181else 
    182182  write(*,*) "phyetat0: Bare ground albedo <albedodat> range:", & 
     
    188188if (.not.found) then 
    189189  write(*,*) "phyetat0: Failed loading <ZMEA>" 
    190   call abort 
     190  call abort_physiq 
    191191else 
    192192  write(*,*) "phyetat0: <ZMEA> range:", & 
     
    198198if (.not.found) then 
    199199  write(*,*) "phyetat0: Failed loading <ZSTD>" 
    200   call abort 
     200  call abort_physiq 
    201201else 
    202202  write(*,*) "phyetat0: <ZSTD> range:", & 
     
    208208if (.not.found) then 
    209209  write(*,*) "phyetat0: Failed loading <ZSIG>" 
    210   call abort 
     210  call abort_physiq 
    211211else 
    212212  write(*,*) "phyetat0: <ZSIG> range:", & 
     
    218218if (.not.found) then 
    219219  write(*,*) "phyetat0: Failed loading <ZGAM>" 
    220   call abort 
     220  call abort_physiq 
    221221else 
    222222  write(*,*) "phyetat0: <ZGAM> range:", & 
     
    228228if (.not.found) then 
    229229  write(*,*) "phyetat0: Failed loading <ZTHE>" 
    230   call abort 
     230  call abort_physiq 
    231231else 
    232232  write(*,*) "phyetat0: <ZTHE> range:", & 
     
    238238if (.not.found) then 
    239239  write(*,*) "phyetat0: Failed loading <tsurf>" 
    240   call abort 
     240  call abort_physiq 
    241241else 
    242242  write(*,*) "phyetat0: Surface temperature <tsurf> range:", & 
     
    248248if (.not.found) then 
    249249  write(*,*) "phyetat0: Failed loading <emis>" 
    250   call abort 
     250  call abort_physiq 
    251251else 
    252252  write(*,*) "phyetat0: Surface emissivity <emis> range:", & 
     
    258258if (.not.found) then 
    259259  write(*,*) "phyetat0: Failed loading <cloudfrac>" 
    260   call abort 
     260  call abort_physiq 
    261261else 
    262262  write(*,*) "phyetat0: Cloud fraction <cloudfrac> range:", & 
     
    268268if (.not.found) then 
    269269  write(*,*) "phyetat0: Failed loading <totcloudfrac>" 
    270   call abort 
     270  call abort_physiq 
    271271else 
    272272  write(*,*) "phyetat0: Total cloud fraction <totcloudfrac> range:", & 
     
    278278if (.not.found) then 
    279279  write(*,*) "phyetat0: Failed loading <hice>" 
    280 !  call abort 
     280!  call abort_physiq 
    281281      do ig=1,ngrid 
    282282      hice(ig)=0. 
     
    361361if (.not.found) then 
    362362  write(*,*) "phyetat0: Failed loading <q2>" 
    363   call abort 
     363  call abort_physiq 
    364364else 
    365365  write(*,*) "phyetat0: PBL wind variance <q2> range:", & 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/physiq.F90

    r310 r313  
    587587           if (is_master) write(*,*) "taking dynamics day for physics:  ",day_ini 
    588588           day_ini=pday 
    589 !ym           stop 
     589!ym           CALL abort_physiq 
    590590         endif 
    591591 
     
    670670              if (is_master) write(*,*) "physiq: Error! No num_run file!" 
    671671              if (is_master) write(*,*) " (which is needed for sourceevol option)" 
    672               stop 
     672              CALL abort_physiq 
    673673            endif 
    674674            read(128,*) num_run  
     
    797797        print*,'I need values for flatten, J2, Rmean and MassPlanet to compute glat (else set oblate=.false.)' 
    798798 
    799         call abort 
     799        call abort_physiq 
    800800        else 
    801801 
     
    940940              if(kastprof)then 
    941941                 print*,'kastprof should not = true here' 
    942                  call abort 
     942                 call abort_physiq 
    943943              endif 
    944944              if(water) then 
     
    12871287         if (.not.tracer) then 
    12881288            print*,'We need a CO2 ice tracer to condense CO2' 
    1289             call abort 
     1289            call abort_physiq 
    12901290         endif 
    12911291         call condense_cloud(ngrid,nlayer,nq,ptimestep,   & 
     
    13921392                  call planetwide_sumval(cpp*massarea(:,:)*dtlscale(:,:)/totarea_planet,dEtot) 
    13931393!                 if(isnan(dEtot)) then ! NB: isnan() is not a standard function... 
    1394 !                    print*,'Nan in largescale, abort' 
    1395 !                     STOP 
     1394!                    print*,'Nan in largescale, abort_physiq' 
     1395!                     CALL abort_physiq 
    13961396!                 endif 
    13971397                  if (is_master) print*,'In largescale atmospheric energy change =',dEtot,' W m-2' 
     
    17941794               print*,'temp=   ',pt(ig,:) 
    17951795               print*,'pplay=  ',pplay(ig,:) 
    1796                call abort 
     1796               call abort_physiq 
    17971797            endif 
    17981798         end do 
     
    18441844         print*,'As testradtimes enabled,' 
    18451845         print*,'exiting physics on first call' 
    1846          call abort 
     1846         call abort_physiq 
    18471847      endif 
    18481848 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/profile.F

    r222 r313  
    184184 
    185185      GOTO 201 
    186 101   STOP'fichier profile inexistant' 
     186101   PRINT*, 'fichier profile inexistant' 
     187      CALL abort_physiq 
    187188201   CONTINUE 
    188189      CLOSE(10) 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/radii_mod.F90

    r298 r313  
    9393               print*,'The code still needs generalisation to arbitrary' 
    9494               print*,'aerosol kinds and number.' 
    95                call abort 
     95               call abort_physiq 
    9696            endif 
    9797 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/rain.F90

    r227 r313  
    370370         if(zrfl(i).lt.0.0)then 
    371371            print*,'Droplets of negative rain are falling...' 
    372             call abort 
     372            call abort_physiq 
    373373         endif 
    374374         IF (t(i,1) .LT. T_h2O_ice_liq) THEN 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/setspi.F90

    r298 r313  
    9090         write(*,*)' datadir = /absolute/path/to/datagcm' 
    9191         write(*,*)'Also check that the corrkdir you chose in callphys.def exists.' 
    92          call abort 
     92         call abort_physiq 
    9393      endif 
    9494     
     
    110110      if(nb.ne.L_NSPECTI) then 
    111111         write(*,*) 'MISMATCH !! I stop here' 
    112          call abort 
     112         call abort_physiq 
    113113      endif 
    114114 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/setspv.F90

    r298 r313  
    6868         write(*,*)' datadir = /absolute/path/to/datagcm' 
    6969         write(*,*)'Also check that the corrkdir you chose in callphys.def exists.' 
    70          call abort 
     70         call abort_physiq 
    7171      endif 
    7272         
     
    8787      if(nb.ne.L_NSPECTV) then 
    8888         write(*,*) 'MISMATCH !! I stop here' 
    89          call abort 
     89         call abort_physiq 
    9090      endif 
    9191 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/soil_settings.F

    r222 r313  
    102102          if (ierr.ne.0) then 
    103103            write(*,*) 'soil_settings: failed allocation of oldmlayer!' 
    104             stop 
     104            CALL abort_physiq 
    105105          endif 
    106106        endif 
     
    171171       if (.not.found) then 
    172172         write(*,*) "soil_settings: Failed loading <inertiedat>" 
    173          call abort 
     173         call abort_physiq 
    174174       endif 
    175175        
     
    188188            write(*,*) 'soil_settings: failed allocation of ', 
    189189     &                 'oldinertiedat!' 
    190             stop 
     190            CALL abort_physiq 
    191191           endif 
    192192         endif ! of if (.not.allocated(oldinertiedat)) 
     
    194194        if (.not.found) then 
    195195          write(*,*) "soil_settings: Failed loading <inertiedat>" 
    196           call abort 
     196          call abort_physiq 
    197197        endif 
    198198       else ! put values in therm_i 
     
    200200         if (.not.found) then 
    201201           write(*,*) "soil_settings: Failed loading <inertiedat>" 
    202            call abort 
     202           call abort_physiq 
    203203         endif 
    204204!        endif 
     
    224224             write(*,*) 'soil_settings: failed allocation of ', 
    225225     &                  'oldtsoil!' 
    226              stop 
     226             CALL abort_physiq 
    227227           endif 
    228228         endif 
     
    230230         if (.not.found) then 
    231231           write(*,*) "soil_settings: Failed loading <tsoil>" 
    232            call abort 
     232           call abort_physiq 
    233233         endif 
    234234       else ! put values in tsoil 
     
    236236         if (.not.found) then 
    237237           write(*,*) "soil_settings: Failed loading <tsoil>" 
    238            call abort 
     238           call abort_physiq 
    239239         endif 
    240240       endif ! of if (interpol)  
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/start2archive.F

    r227 r313  
    176176       IF (ierr.NE.NF_NOERR) THEN 
    177177         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom) 
    178         CALL ABORT 
     178        CALL abort_physiq 
    179179       ENDIF 
    180180                                                 
     
    182182      IF (ierr .NE. NF_NOERR) THEN 
    183183       PRINT*, "start2archive: Le champ <controle> est absent" 
    184        CALL abort 
     184       CALL abort_physiq 
    185185      ENDIF 
    186186#ifdef NC_DOUBLE 
     
    191191       IF (ierr .NE. NF_NOERR) THEN 
    192192          PRINT*, "start2archive: Lecture echoue pour <controle>" 
    193           CALL abort 
     193          CALL abort_physiq 
    194194       ENDIF 
    195195 
     
    217217       IF (ierr.NE.NF_NOERR) THEN 
    218218         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom) 
    219         CALL ABORT 
     219        CALL abort_physiq 
    220220       ENDIF 
    221221                                                 
     
    223223      IF (ierr .NE. NF_NOERR) THEN 
    224224       PRINT*, "start2archive: Le champ <controle> est absent" 
    225        CALL abort 
     225       CALL abort_physiq 
    226226      ENDIF 
    227227#ifdef NC_DOUBLE 
     
    232232       IF (ierr .NE. NF_NOERR) THEN 
    233233          PRINT*, "start2archive: Lecture echoue pour <controle>" 
    234           CALL abort 
     234          CALL abort_physiq 
    235235       ENDIF 
    236236 
     
    242242c----------------------------------------------------------------------- 
    243243!mars a voir      if ((day_ini_fi.ne.day_ini).or.(abs(timefi-timedyn).gt.1.e-10))  
    244       if ((day_ini_fi.ne.day_ini))  
    245      &  stop ' Probleme de Synchro entre start et startfi !!!' 
     244      if ((day_ini_fi.ne.day_ini)) THEN 
     245        PRINT*, 'Probleme de Synchro entre start et startfi !!!' 
     246        CALL abort_physiq 
     247      endif 
    246248 
    247249 
     
    401403      if (ierr.ne.NF_NOERR) then 
    402404         write(*,*) "time matter ",NF_STRERROR(ierr) 
    403          stop 
     405         CALL abort_physiq 
    404406      endif 
    405407 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/su_gases.F90

    r227 r313  
    3030        write(*,*) "sugases.F90: error reading number of gases" 
    3131        write(*,*) "   (first line of gases.def) " 
    32         call abort 
     32        call abort_physiq 
    3333     endif 
    3434 
     
    4040        if (ierr.ne.0) then 
    4141           write(*,*) 'sugases.F90: error reading gas names in gases.def...' 
    42            call abort 
     42           call abort_physiq 
    4343        endif 
    4444     enddo                  !of do igas=1,ngasmx 
     
    5050        if (ierr.ne.0) then 
    5151           write(*,*) 'sugases.F90: error reading gas molar fractions in gases.def...' 
    52            call abort 
     52           call abort_physiq 
    5353        endif 
    5454 
     
    6060              print*,'You seem to be choosing two variable gases' 
    6161              print*,'Check that gases.def is correct' 
    62               call abort 
     62              call abort_physiq 
    6363           endif 
    6464        endif 
     
    120120  else 
    121121     write(*,*) 'Cannot find required file "gases.def"' 
    122      call abort 
     122     call abort_physiq 
    123123  endif 
    124124  close(90) 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/suaer_corrk.F90

    r298 r313  
    222222               write(*,*)' http://www.lmd.jussieu.fr/',& 
    223223               '~forget/datagcm/datafile' 
    224                CALL ABORT  
     224               CALL abort_physiq  
    225225            ENDIF 
    226226            OPEN(UNIT=file_unit,& 
     
    248248               WRITE(*,*) 'readoptprop: ',&  
    249249               'Error while loading optical properties.'  
    250                CALL ABORT  
     250               CALL abort_physiq  
    251251            END SELECT reading1_seq ! ============================== 
    252252         ENDIF 
     
    323323         WRITE(*,*) 'readoptprop: ',& 
    324324         'Error while loading optical properties.' 
    325          CALL ABORT 
     325         CALL abort_physiq 
    326326      END SELECT reading2_seq   ! ============================== 
    327327      ENDIF 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/tabfi.F

    r298 r313  
    164164       if (.not.found) then 
    165165         write(*,*)"tabfi: Failed reading <controle> array" 
    166          call abort 
     166         call abort_physiq 
    167167       else 
    168168         if (is_master) write(*,*)'tabfi: tab_cntrl',tab_cntrl 
     
    276276        write(*,*) "tabfi: Error modifying tab_control should", 
    277277     &             " only happen in serial mode (eg: by newstart)" 
    278         stop 
     278        CALL abort_physiq 
    279279      endif 
    280280c----------------------------------------------------------------------- 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/vlz_fi.F

    r227 r313  
    169169c               wq(ij,l+1)= (MQtot + (-w(ij,l+1)-Mtot)*qm(ij,1)) 
    170170                write(*,*) 'a rather weird situation in vlz_fi !' 
    171                 stop 
     171                CALL abort_physiq 
    172172             end if 
    173173          endif 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/write_archive.F

    r222 r313  
    115115              write(*,*) "***** PUT_VAR matter in write_archive" 
    116116              write(*,*) "***** with ",nom," ",nf_STRERROR(ierr) 
    117               call abort 
     117              call abort_physiq 
    118118           endif 
    119119 
     
    134134           write(*,*)"write_archive: dimension <subsurface_layers>", 
    135135     &               " is missing !!!" 
    136            call abort 
     136           call abort_physiq 
    137137          endif 
    138138          ierr=NF_INQ_DIMID(nid,"Time",id(4)) 
     
    202202              write(*,*) "***** PUT_VAR matter in write_archive" 
    203203              write(*,*) "***** with ",nom,nf_STRERROR(ierr) 
    204               call abort 
     204              call abort_physiq 
    205205           endif 
    206206 
     
    238238              write(*,*) "***** PUT_VAR matter in write_archive" 
    239239              write(*,*) "***** with ",nom,nf_STRERROR(ierr) 
    240               call abort 
     240              call abort_physiq 
    241241           endif 
    242242 
    243243        else 
    244244          write(*,*) "write_archive: dim=",dim," ?!?" 
    245           call abort 
     245          call abort_physiq 
    246246        endif ! of if (dim.eq.3) else if (dim.eq.-3) .... 
    247247 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/writediagfi.F

    r253 r313  
    150150            if (n.ge.n_nom_def_max) then 
    151151               write(*,*)"n_nom_def_max too small in writediagfi.F:",n 
    152                stop 
     152               CALL abort_physiq 
    153153            end if  
    154154            n_nom_def=n-1 
     
    183183           write(*,*) "   firstnom string not long enough!!" 
    184184           write(*,*) "   increase its size to at least ",len_trim(nom) 
    185            stop 
     185           CALL abort_physiq 
    186186         endif 
    187187          
     
    457457           write(*,*) "writediagfi error: dim=1 not implemented ", 
    458458     &                 "in parallel mode" 
    459            stop 
     459           CALL abort_physiq 
    460460         endif 
    461461!         Passage variable physique -->  physique dynamique 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/writediagsoil.F90

    r245 r313  
    7777    write(*,*) "   firstname string not long enough!!" 
    7878    write(*,*) "   increase its size to at least ",len_trim(name) 
    79     stop 
     79    CALL abort_physiq 
    8080  endif 
    8181   
     
    8989   if (ierr.ne.NF_NOERR) then 
    9090    write(*,*)'writediagsoil: Error, failed creating file '//trim(filename) 
    91     stop 
     91    CALL abort_physiq 
    9292   endif 
    9393  endif ! of if (is_master) 
     
    133133     if (ierr.ne.NF_NOERR) then 
    134134      write(*,*)"writediagsoil: Failed writing date to time variable" 
    135       stop  
     135      CALL abort_physiq  
    136136     endif 
    137137    endif ! of if (is_master) 
     
    285285#ifdef CPP_PARA 
    286286  write(*,*) "writediagsoil: dimps==0 case not implemented in // mode!!" 
    287   stop 
     287  CALL abort_physiq 
    288288#endif 
    289289  ! A. Copy data value 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/writediagspecIR.F

    r245 r313  
    138138           write(*,*) "   firstnom string not long enough!!" 
    139139           write(*,*) "   increase its size to at least ",len_trim(nom) 
    140            stop 
     140           CALL abort_physiq 
    141141         endif 
    142142 
     
    214214              write(*,*) "***** with time" 
    215215              write(*,*) 'ierr=', ierr    
    216 c             call abort 
     216c             call abort_physiq 
    217217             endif 
    218218 
     
    295295              write(*,*) "***** with ",nom 
    296296              write(*,*) 'ierr=', ierr 
    297              call abort 
     297             call abort_physiq 
    298298           endif  
    299299 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/writediagspecVI.F

    r245 r313  
    137137           write(*,*) "   firstnom string not long enough!!" 
    138138           write(*,*) "   increase its size to at least ",len_trim(nom) 
    139            stop 
     139           CALL abort_physiq 
    140140         endif 
    141141 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/wstats.F90

    r245 r313  
    222222      if (ierr.ne.NF_NOERR) then 
    223223         write (*,*) NF_STRERROR(ierr) 
    224          stop "" 
     224         CALL abort_physiq 
    225225      endif 
    226226 
     
    237237      if (ierr.ne.NF_NOERR) then 
    238238         write (*,*) NF_STRERROR(ierr) 
    239          stop "" 
     239         CALL abort_physiq 
    240240      endif 
    241241   endif 
     
    405405   write(*,*) "def_var_stats: Failed defining variable "//trim(name) 
    406406   write(*,*) NF_STRERROR(ierr) 
    407    stop "" 
     407   CALL abort_physiq 
    408408endif 
    409409 
     
    414414   write(*,*) "def_var_stats: Failed writing title attribute for "//trim(name) 
    415415   write(*,*) NF_STRERROR(ierr) 
    416    stop "" 
     416   CALL abort_physiq 
    417417endif 
    418418 
     
    422422   write(*,*) "def_var_stats: Failed writing units attribute for "//trim(name) 
    423423   write(*,*) NF_STRERROR(ierr) 
    424    stop "" 
     424   CALL abort_physiq 
    425425endif 
    426426 
  • codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/xios_output.F90

    r270 r313  
    1414CONTAINS 
    1515 
    16   SUBROUTINE initialize_xios_output 
     16  SUBROUTINE initialize_xios_output(time) 
    1717  USE comgeomphy 
    1818  USE xios 
     
    2424  IMPLICIT NONE 
    2525    INCLUDE "comcstfi.h"  
    26        
     26    INTEGER,INTENT(IN) :: time   
    2727    TYPE(xios_context) :: ctx_hdl 
    2828    TYPE(xios_time)      :: dtime 
     
    3535    INTEGER :: l 
    3636    REAL :: presnivs(klev) 
     37    INTEGER :: time0 
     38    CHARACTER(LEN=256) :: start_date 
     39    INTEGER :: year,month,day,hour,minute,second 
    3740 
    3841    CALL gather_omp(rlond,lon_mpi) 
     
    4346!$OMP BARRIER     
    4447!$OMP MASTER 
     48    time0=time 
     49    year=time0/(86400*360) 
     50    time0=time0-year*(86400*360) 
     51    month=time0/(86400*30) 
     52    time0=time0-month*(86400*30) 
     53    month=month+1 
     54    day=time0/86400 
     55    time0=time0-day*86400 
     56    day=day+1 
     57    hour=time0/3600 
     58    time0=time0-hour*3600 
     59    minute=time0/60 
     60    time0=time0-minute*60 
     61    second=time0 
     62    write(start_date,'(i0.4,"-",i0.2,"-",i0.2," ",i0.2,":",i0.2,":",i0.2)'),year,month,day,hour,minute,second 
     63     
     64    PRINT *,"time0  ",time," Start Date ",TRIM(start_date) 
    4565    CALL xios_context_initialize(context_id,comm_lmdz_phy) 
    4666    CALL xios_get_handle(context_id, ctx_hdl) 
    4767    CALL xios_set_current_context(ctx_hdl) 
     68    CALL xios_set_attr(ctx_hdl,start_date=TRIM(start_date)) 
    4869    
    4970!    lev_value(:) = (/ (l,l=1,klev) /)      
Note: See TracChangeset for help on using the changeset viewer.