Ignore:
Timestamp:
03/12/07 17:01:04 (17 years ago)
Author:
bellier
Message:

JB: on the road to svn

File:
1 edited

Legend:

Unmodified
Added
Removed
  • IOIPSL/trunk/src/errioipsl.f90

    • Property svn:keywords set to Id
    r4 r11  
    1 !$Header: /home/ioipsl/CVSROOT/IOIPSL/src/errioipsl.f90,v 2.2 2005/02/22 10:14:14 adm Exp $ 
     1!$Id$ 
    22!- 
    33MODULE errioipsl 
     
    77PRIVATE 
    88!- 
    9 PUBLIC :: ipslnlf, ipslerr, histerr, ipsldbg 
    10 !- 
    11   INTEGER :: n_l=6 
    12   LOGICAL :: ioipsl_debug=.FALSE. 
     9PUBLIC :: ipslnlf, ipslerr, ipslerr_act, ipslerr_inq, histerr, ipsldbg 
     10!- 
     11  INTEGER :: n_l=6, ilv_cur=0, ilv_max=0 
     12  LOGICAL :: ioipsl_debug=.FALSE., lact_mode=.TRUE. 
    1313!- 
    1414!=== 
     
    1818!!-------------------------------------------------------------------- 
    1919!! The "ipslnlf" routine allows to know and modify 
    20 !! the current logical number for the messages, 
     20!! the current logical number for the messages. 
    2121!! 
    2222!! SUBROUTINE ipslnlf (new_number,old_number) 
     
    7171!--------------------------------------------------------------------- 
    7272   IF ( (plev >= 1).AND.(plev <= 3) ) THEN 
     73     ilv_cur = plev 
     74     ilv_max = MAX(ilv_max,plev) 
    7375     WRITE(n_l,'(/,A," ",A)') TRIM(pemsg(plev)),TRIM(pcname) 
    7476     WRITE(n_l,'(3(" --> ",A,/))') TRIM(pstr1),TRIM(pstr2),TRIM(pstr3) 
    7577   ENDIF 
    76    IF (plev == 3) THEN 
     78   IF ( (plev == 3).AND.lact_mode) THEN 
    7779     STOP 'Fatal error from IOIPSL. See stdout for more details' 
    7880   ENDIF 
    7981!--------------------- 
    8082END SUBROUTINE ipslerr 
     83!=== 
     84SUBROUTINE ipslerr_act (new_mode,old_mode) 
     85!!-------------------------------------------------------------------- 
     86!! The "ipslerr_act" routine allows to know and modify 
     87!! the current "action mode" for the error messages, 
     88!! and reinitialize the error level values. 
     89!! 
     90!! SUBROUTINE ipslerr_act (new_mode,old_mode) 
     91!! 
     92!! Optional INPUT argument 
     93!! 
     94!! (I) new_mode : new error action mode 
     95!!                .TRUE.  -> STOP     in case of fatal error 
     96!!                .FALSE. -> CONTINUE in case of fatal error 
     97!! 
     98!! Optional OUTPUT argument 
     99!! 
     100!! (I) old_mode : current error action mode 
     101!!-------------------------------------------------------------------- 
     102  IMPLICIT NONE 
     103!- 
     104  LOGICAL,OPTIONAL,INTENT(IN)  :: new_mode 
     105  LOGICAL,OPTIONAL,INTENT(OUT) :: old_mode 
     106!--------------------------------------------------------------------- 
     107  IF (PRESENT(old_mode)) THEN 
     108    old_mode = lact_mode 
     109  ENDIF 
     110  IF (PRESENT(new_mode)) THEN 
     111    lact_mode = new_mode 
     112  ENDIF 
     113  ilv_cur = 0 
     114  ilv_max = 0 
     115!------------------------- 
     116END SUBROUTINE ipslerr_act 
     117!=== 
     118SUBROUTINE ipslerr_inq (current_level,maximum_level) 
     119!!-------------------------------------------------------------------- 
     120!! The "ipslerr_inq" routine allows to know 
     121!! the current level of the error messages 
     122!! and the maximum level encountered since the 
     123!! last call to "ipslerr_act". 
     124!! 
     125!! SUBROUTINE ipslerr_inq (current_level,maximum_level) 
     126!! 
     127!! Optional OUTPUT argument 
     128!! 
     129!! (I) current_level : current error level 
     130!! (I) maximum_level : maximum error level 
     131!!-------------------------------------------------------------------- 
     132  IMPLICIT NONE 
     133!- 
     134  INTEGER,OPTIONAL,INTENT(OUT) :: current_level,maximum_level 
     135!--------------------------------------------------------------------- 
     136  IF (PRESENT(current_level)) THEN 
     137    current_level = ilv_cur 
     138  ENDIF 
     139  IF (PRESENT(maximum_level)) THEN 
     140    maximum_level = ilv_max 
     141  ENDIF 
     142!------------------------- 
     143END SUBROUTINE ipslerr_inq 
    81144!=== 
    82145SUBROUTINE histerr (plev,pcname,pstr1,pstr2,pstr3) 
Note: See TracChangeset for help on using the changeset viewer.