Changeset 169 in lmdz_wrf for branches


Ignore:
Timestamp:
Aug 12, 2014, 11:17:07 AM (10 years ago)
Author:
lfita
Message:

Addig new 'abort_gcm_point', 'abort_gcm_2Dpoint' more informative subroutines

Location:
branches/LMDZ_WRFmeas_develop/WRFV3/lmdz
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/LMDZ_WRFmeas_develop/WRFV3/lmdz/abort_gcm.F90

    r168 r169  
    4848
    4949! L. Fita, LMD. August 2014
    50       SUBROUTINE abort_gcm_point(modname, message, ierr, point)
     50      SUBROUTINE abort_gcm_point(modname, message, ierr, point, val, i1fc, thres)
    5151     
    5252#ifdef CPP_IOIPSL
     
    6666!C         ierr    = severity of situation ( = 0 normal )
    6767!C         point   = 1D point where the error ocurred
     68!C         val     = wrong value
     69!C         if1c    = condition as 1 character
     70!C         thres   = threshold value
    6871
    6972      character(len=*) modname
     
    7174      character(len=*) message
    7275      INTEGER, INTENT(IN)                                :: point
     76      REAL, INTENT(IN)                                   :: val, thres
     77      CHARACTER(LEN=1), INTENT(IN)                       :: if1c
    7378
    7479      write(lunout,*) 'in abort_gcm'
     
    8388!c     call histclo(5)
    8489      write(lunout,*) 'Stopping in ', modname
    85       write(lunout,*) 'Stopping at point ', point
     90      write(lunout,*) 'Stopping at point ', point,' wrong: ',val, if1c, thres
    8691      write(lunout,*) 'Reason = ',message
    8792      if (ierr .eq. 0) then
     
    95100
    96101! L. Fita, LMD. August 2014
    97       SUBROUTINE abort_gcm_2Dpoint(modname, message, ierr, point)
     102      SUBROUTINE abort_gcm_2Dpoint(modname, message, ierr, pk, pl, val, i1fc, thres)
    98103     
    99104#ifdef CPP_IOIPSL
     
    112117!C         message = stuff to print
    113118!C         ierr    = severity of situation ( = 0 normal )
    114 !C         point   = 2D point where the error ocurred
     119!C         pk, pl  = 2D point where the error ocurred (klev, klon)
     120!C         val     = wrong value
     121!C         if1c    = condition as 1 character
     122!C         thres   = threshold value
    115123
    116124      character(len=*) modname
    117125      integer ierr
    118126      character(len=*) message
    119       INTEGER, DIMENSION(2), INTENT(IN)                  :: point
     127      INTEGER, INTENT(IN)                                :: pk, pl
     128      REAL, INTENT(IN)                                   :: val, thres
     129      CHARACTER(LEN=1), INTENT(IN)                       :: if1c
    120130
    121131      write(lunout,*) 'in abort_gcm'
     
    130140!c     call histclo(5)
    131141      write(lunout,*) 'Stopping in ', modname
    132       write(lunout,*) 'Stopping at point (klon, klev)', point
     142      write(lunout,*) 'Stopping at point (klon, klev):', pk, ',', pl,' wrong: ',val, &
     143        if1c, thres
    133144      write(lunout,*) 'Reason = ',message
    134145      if (ierr .eq. 0) then
  • branches/LMDZ_WRFmeas_develop/WRFV3/lmdz/thermcellV0_main.F90

    r1 r169  
    607607           zcon2(ig)=zlay(ig,nlay)-(pcon(ig)-pplay(ig,nlay))/(RG*rho(ig,nlay))/100.
    608608           abort_message = 'thermcellV0_main: les thermiques vont trop haut '
    609            CALL abort_gcm (modname,abort_message,1)
     609! L. Fita, LMD August 2014. Replacing by something more informative
     610!           CALL abort_gcm (modname,abort_message,1)
     611           CALL abort_gcm_point (modname,abort_message,1,ig,pcon(ig),'<',            &
     612             pplay(ig,nlay))
    610613        endif
    611614      enddo
     
    900903                print*,'wmax_sec',wmax_sec(ig)
    901904                abort_message = 'zdenom<1.e-14'
    902                 CALL abort_gcm (modname,abort_message,1)
     905! L. Fita, LMD August 2014. Changing it for something more informative
     906!                CALL abort_gcm (modname,abort_message,1)
     907                CALL abort_gcm_point (modname,abort_message,1,ig,zdenom,'<',1.e-14)
     908
    903909             endif
    904910             if ((zmax_sec(ig).gt.1.e-10).and.(iflag_thermals_ed.eq.0)) then
  • branches/LMDZ_WRFmeas_develop/WRFV3/lmdz/thermcell_dq.F90

    r166 r169  
    5454               print*,'entr dt > m ',entr(ig,k)*ptimestep,masse(ig,k)
    5555               abort_message = ''
    56                PRINT *,'  Lluis aborting at :', ig, k
    57                CALL abort_gcm (modname,abort_message,1)
     56! L. Fita, LMD. August 2014. Changing for something more informative
     57!               CALL abort_gcm (modname,abort_message,1)
     58               CALL abort_gcm_2Dpoint (modname,abort_message,1,ig,k,entr(ig,k),'>',zzm)
    5859            endif
    5960         enddo
     
    189190               print*,'entr dt > m ',entr(ig,k)*ptimestep,masse(ig,k)
    190191               abort_message = ''
    191                PRINT *,'  Lluis aborting at :', ig, k
    192                CALL abort_gcm (modname,abort_message,1)
     192! L. Fita, LMD August 2014. Changing for something more informative
     193!               CALL abort_gcm (modname,abort_message,1)
     194               CALL abort_gcm_2Dpoint (modname,abort_message,1,ig,k,entr(ig,k),'>',  &
     195                 zzm)
    193196            endif
    194197         enddo
  • branches/LMDZ_WRFmeas_develop/WRFV3/lmdz/thermcell_main.F90

    r166 r169  
    721721        if (pcon(ig).le.pplay(ig,nlay)) then
    722722           zcon2(ig)=zlay(ig,nlay)-(pcon(ig)-pplay(ig,nlay))/(RG*rho(ig,nlay))/100.
    723            PRINT *,'  Lluis aborting at :', ig
     723           abort_message = 'thermcellV0_main: les thermiques vont trop haut '
     724! L. Fita, LMD. August 2014. Including something more informative
     725           CALL abort_gcm_point (modname,abort_message,1,ig,pcon(ig),'<',            &
     726             pplay(ig,nlay))
    724727           ierr=1
    725728        endif
Note: See TracChangeset for help on using the changeset viewer.