source: LMDZ6/branches/Amaury_dev/libf/misc/lmdz_assert.f90 @ 5204

Last change on this file since 5204 was 5160, checked in by abarral, 7 weeks ago

Put .h into modules

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 1.9 KB
RevLine 
[1157]1! $Id$
[5113]2MODULE lmdz_assert
[1157]3
[5119]4  IMPLICIT NONE; PRIVATE
5  PUBLIC assert
[1157]6  INTERFACE assert
[5113]7    MODULE PROCEDURE assert1, assert2, assert3, assert4, assert_v
[1157]8  END INTERFACE
9
10CONTAINS
11
[5113]12  SUBROUTINE assert1(n1, string)
13    CHARACTER(LEN = *), INTENT(IN) :: string
[1157]14    LOGICAL, INTENT(IN) :: n1
[5117]15    IF (.NOT. n1) THEN
[5113]16      write (*, *) 'nrerror: an assertion failed with this tag:', &
17              string
[5160]18      PRINT *, 'program terminated by assert1'
[5113]19      stop 1
[1157]20    end if
21  END SUBROUTINE assert1
22  !BL
[5113]23  SUBROUTINE assert2(n1, n2, string)
24    CHARACTER(LEN = *), INTENT(IN) :: string
25    LOGICAL, INTENT(IN) :: n1, n2
[5117]26    IF (.NOT. (n1 .AND. n2)) THEN
[5113]27      write (*, *) 'nrerror: an assertion failed with this tag:', &
28              string
[5160]29      PRINT *, 'program terminated by assert2'
[5113]30      stop 1
[1157]31    end if
32  END SUBROUTINE assert2
33  !BL
[5113]34  SUBROUTINE assert3(n1, n2, n3, string)
35    CHARACTER(LEN = *), INTENT(IN) :: string
36    LOGICAL, INTENT(IN) :: n1, n2, n3
[5117]37    IF (.NOT. (n1 .AND. n2 .AND. n3)) THEN
[5113]38      write (*, *) 'nrerror: an assertion failed with this tag:', &
39              string
[5160]40      PRINT *, 'program terminated by assert3'
[5113]41      stop 1
[1157]42    end if
43  END SUBROUTINE assert3
44  !BL
[5113]45  SUBROUTINE assert4(n1, n2, n3, n4, string)
46    CHARACTER(LEN = *), INTENT(IN) :: string
47    LOGICAL, INTENT(IN) :: n1, n2, n3, n4
[5117]48    IF (.NOT. (n1 .AND. n2 .AND. n3 .AND. n4)) THEN
[5113]49      write (*, *) 'nrerror: an assertion failed with this tag:', &
50              string
[5160]51      PRINT *, 'program terminated by assert4'
[5113]52      stop 1
[1157]53    end if
54  END SUBROUTINE assert4
55  !BL
[5113]56  SUBROUTINE assert_v(n, string)
57    CHARACTER(LEN = *), INTENT(IN) :: string
[1157]58    LOGICAL, DIMENSION(:), INTENT(IN) :: n
[5117]59    IF (.NOT. all(n)) THEN
[5113]60      write (*, *) 'nrerror: an assertion failed with this tag:', &
61              string
[5160]62      PRINT *, 'program terminated by assert_v'
[5113]63      stop 1
[1157]64    end if
65  END SUBROUTINE assert_v
66
[5113]67END MODULE lmdz_assert
Note: See TracBrowser for help on using the repository browser.