Ignore:
Timestamp:
Jul 24, 2024, 1:17:08 PM (2 months ago)
Author:
abarral
Message:

Rename modules in misc from *_mod > lmdz_*
Put cbrt.f90, ch*.f90, pch*.f90 in new lmdz_libmath_pch.f90

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/misc/lmdz_assert.f90

    r5112 r5113  
    11! $Id$
    2 MODULE assert_m
     2MODULE lmdz_assert
    33
    4   implicit none
     4  IMPLICIT NONE
    55
    66  INTERFACE assert
    7      MODULE PROCEDURE assert1,assert2,assert3,assert4,assert_v
     7    MODULE PROCEDURE assert1, assert2, assert3, assert4, assert_v
    88  END INTERFACE
    99
    10   private assert1,assert2,assert3,assert4,assert_v
     10  PRIVATE assert1, assert2, assert3, assert4, assert_v
    1111
    1212CONTAINS
    1313
    14   SUBROUTINE assert1(n1,string)
    15     CHARACTER(LEN=*), INTENT(IN) :: string
     14  SUBROUTINE assert1(n1, string)
     15    CHARACTER(LEN = *), INTENT(IN) :: string
    1616    LOGICAL, INTENT(IN) :: n1
    1717    if (.not. n1) then
    18        write (*,*) 'nrerror: an assertion failed with this tag:', &
    19             string
    20        print *, 'program terminated by assert1'
    21        stop 1
     18      write (*, *) 'nrerror: an assertion failed with this tag:', &
     19              string
     20      print *, 'program terminated by assert1'
     21      stop 1
    2222    end if
    2323  END SUBROUTINE assert1
    2424  !BL
    25   SUBROUTINE assert2(n1,n2,string)
    26     CHARACTER(LEN=*), INTENT(IN) :: string
    27     LOGICAL, INTENT(IN) :: n1,n2
     25  SUBROUTINE assert2(n1, n2, string)
     26    CHARACTER(LEN = *), INTENT(IN) :: string
     27    LOGICAL, INTENT(IN) :: n1, n2
    2828    if (.not. (n1 .and. n2)) then
    29        write (*,*) 'nrerror: an assertion failed with this tag:', &
    30             string
    31        print *, 'program terminated by assert2'
    32        stop 1
     29      write (*, *) 'nrerror: an assertion failed with this tag:', &
     30              string
     31      print *, 'program terminated by assert2'
     32      stop 1
    3333    end if
    3434  END SUBROUTINE assert2
    3535  !BL
    36   SUBROUTINE assert3(n1,n2,n3,string)
    37     CHARACTER(LEN=*), INTENT(IN) :: string
    38     LOGICAL, INTENT(IN) :: n1,n2,n3
     36  SUBROUTINE assert3(n1, n2, n3, string)
     37    CHARACTER(LEN = *), INTENT(IN) :: string
     38    LOGICAL, INTENT(IN) :: n1, n2, n3
    3939    if (.not. (n1 .and. n2 .and. n3)) then
    40        write (*,*) 'nrerror: an assertion failed with this tag:', &
    41             string
    42        print *, 'program terminated by assert3'
    43        stop 1
     40      write (*, *) 'nrerror: an assertion failed with this tag:', &
     41              string
     42      print *, 'program terminated by assert3'
     43      stop 1
    4444    end if
    4545  END SUBROUTINE assert3
    4646  !BL
    47   SUBROUTINE assert4(n1,n2,n3,n4,string)
    48     CHARACTER(LEN=*), INTENT(IN) :: string
    49     LOGICAL, INTENT(IN) :: n1,n2,n3,n4
     47  SUBROUTINE assert4(n1, n2, n3, n4, string)
     48    CHARACTER(LEN = *), INTENT(IN) :: string
     49    LOGICAL, INTENT(IN) :: n1, n2, n3, n4
    5050    if (.not. (n1 .and. n2 .and. n3 .and. n4)) then
    51        write (*,*) 'nrerror: an assertion failed with this tag:', &
    52             string
    53        print *, 'program terminated by assert4'
    54        stop 1
     51      write (*, *) 'nrerror: an assertion failed with this tag:', &
     52              string
     53      print *, 'program terminated by assert4'
     54      stop 1
    5555    end if
    5656  END SUBROUTINE assert4
    5757  !BL
    58   SUBROUTINE assert_v(n,string)
    59     CHARACTER(LEN=*), INTENT(IN) :: string
     58  SUBROUTINE assert_v(n, string)
     59    CHARACTER(LEN = *), INTENT(IN) :: string
    6060    LOGICAL, DIMENSION(:), INTENT(IN) :: n
    6161    if (.not. all(n)) then
    62        write (*,*) 'nrerror: an assertion failed with this tag:', &
    63             string
    64        print *, 'program terminated by assert_v'
    65        stop 1
     62      write (*, *) 'nrerror: an assertion failed with this tag:', &
     63              string
     64      print *, 'program terminated by assert_v'
     65      stop 1
    6666    end if
    6767  END SUBROUTINE assert_v
    6868
    69 END MODULE assert_m
     69END MODULE lmdz_assert
Note: See TracChangeset for help on using the changeset viewer.