source: LMDZ5/trunk/tools/Max_diff_nc_with_lib/NR_util/assert.f90 @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

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