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

Last change on this file since 5151 was 5119, checked in by abarral, 18 months ago

enforce PRIVATE by default in several modules, expose PUBLIC as needed
move eigen.f90 to obsolete/
(lint) aslong the way

  • 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
Line 
1! $Id$
2MODULE lmdz_assert
3
4  IMPLICIT NONE; PRIVATE
5  PUBLIC assert
6  INTERFACE assert
7    MODULE PROCEDURE assert1, assert2, assert3, assert4, assert_v
8  END INTERFACE
9
10CONTAINS
11
12  SUBROUTINE assert1(n1, string)
13    CHARACTER(LEN = *), INTENT(IN) :: string
14    LOGICAL, INTENT(IN) :: n1
15    IF (.NOT. n1) THEN
16      write (*, *) 'nrerror: an assertion failed with this tag:', &
17              string
18      print *, 'program terminated by assert1'
19      stop 1
20    end if
21  END SUBROUTINE assert1
22  !BL
23  SUBROUTINE assert2(n1, n2, string)
24    CHARACTER(LEN = *), INTENT(IN) :: string
25    LOGICAL, INTENT(IN) :: n1, n2
26    IF (.NOT. (n1 .AND. n2)) THEN
27      write (*, *) 'nrerror: an assertion failed with this tag:', &
28              string
29      print *, 'program terminated by assert2'
30      stop 1
31    end if
32  END SUBROUTINE assert2
33  !BL
34  SUBROUTINE assert3(n1, n2, n3, string)
35    CHARACTER(LEN = *), INTENT(IN) :: string
36    LOGICAL, INTENT(IN) :: n1, n2, n3
37    IF (.NOT. (n1 .AND. n2 .AND. n3)) THEN
38      write (*, *) 'nrerror: an assertion failed with this tag:', &
39              string
40      print *, 'program terminated by assert3'
41      stop 1
42    end if
43  END SUBROUTINE assert3
44  !BL
45  SUBROUTINE assert4(n1, n2, n3, n4, string)
46    CHARACTER(LEN = *), INTENT(IN) :: string
47    LOGICAL, INTENT(IN) :: n1, n2, n3, n4
48    IF (.NOT. (n1 .AND. n2 .AND. n3 .AND. n4)) THEN
49      write (*, *) 'nrerror: an assertion failed with this tag:', &
50              string
51      print *, 'program terminated by assert4'
52      stop 1
53    end if
54  END SUBROUTINE assert4
55  !BL
56  SUBROUTINE assert_v(n, string)
57    CHARACTER(LEN = *), INTENT(IN) :: string
58    LOGICAL, DIMENSION(:), INTENT(IN) :: n
59    IF (.NOT. all(n)) THEN
60      write (*, *) 'nrerror: an assertion failed with this tag:', &
61              string
62      print *, 'program terminated by assert_v'
63      stop 1
64    end if
65  END SUBROUTINE assert_v
66
67END MODULE lmdz_assert
Note: See TracBrowser for help on using the repository browser.