Ignore:
Timestamp:
Oct 21, 2024, 2:58:45 PM (23 hours ago)
Author:
abarral
Message:

Convert fixed-form to free-form sources .F -> .{f,F}90
(WIP: some .F remain, will be handled in subsequent commits)

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dyn3d_common/laplacien_rotgam.f90

    r5245 r5246  
    22! $Header$
    33!
    4       SUBROUTINE laplacien_rotgam ( klevel, rotin, rotout )
    5 c
    6 c    P. Le Van
    7 c
    8 c   ************************************************************
    9 c   ... calcul de  (rotat x nxgrad)_gam  du rotationnel rotin ..
    10 c   ************************************************************
    11 c    klevel et teta  sont des arguments  d'entree pour le s-prog
    12 c      divgra     est  un argument  de sortie pour le s-prog
    13 c
    14       IMPLICIT NONE
    15 c
    16       INCLUDE "dimensions.h"
    17       INCLUDE "paramet.h"
    18       INCLUDE "comgeom.h"
     4SUBROUTINE laplacien_rotgam ( klevel, rotin, rotout )
     5  !
     6  ! P. Le Van
     7  !
     8  !   ************************************************************
     9  !   ... calcul de  (rotat x nxgrad)_gam  du rotationnel rotin ..
     10  !   ************************************************************
     11  ! klevel et teta  sont des arguments  d'entree pour le s-prog
     12  !  divgra     est  un argument  de sortie pour le s-prog
     13  !
     14  IMPLICIT NONE
     15  !
     16  INCLUDE "dimensions.h"
     17  INCLUDE "paramet.h"
     18  INCLUDE "comgeom.h"
    1919
    20 c
    21 c    .............   variables  en  arguments    ...........
    22 c
    23       INTEGER klevel
    24       REAL rotin( ip1jm,klevel ), rotout( ip1jm,klevel )
    25 c
    26 c   ............     variables   locales     ...............
    27 c
    28       INTEGER l, ij
    29       REAL ghy(ip1jm,llm), ghx(ip1jmp1,llm)
    30 c   ........................................................
    31 c
    32 c
     20  !
     21  !    .............   variables  en  arguments    ...........
     22  !
     23  INTEGER :: klevel
     24  REAL :: rotin( ip1jm,klevel ), rotout( ip1jm,klevel )
     25  !
     26  !   ............     variables   locales     ...............
     27  !
     28  INTEGER :: l, ij
     29  REAL :: ghy(ip1jm,llm), ghx(ip1jmp1,llm)
     30  !   ........................................................
     31  !
     32  !
    3333
    34       CALL   nxgrad_gam ( klevel, rotin,   ghx ,   ghy  )
    35       CALL   rotat_nfil ( klevel, ghx  ,   ghy , rotout )
    36 c
    37       DO l = 1, klevel
    38         DO ij = 1, ip1jm
    39          rotout(ij,l) = rotout(ij,l) * unsairz_gam(ij)
    40         ENDDO
    41       ENDDO
     34  CALL   nxgrad_gam ( klevel, rotin,   ghx ,   ghy  )
     35  CALL   rotat_nfil ( klevel, ghx  ,   ghy , rotout )
     36  !
     37  DO l = 1, klevel
     38    DO ij = 1, ip1jm
     39     rotout(ij,l) = rotout(ij,l) * unsairz_gam(ij)
     40    ENDDO
     41  ENDDO
    4242
    43       RETURN
    44       END
     43  RETURN
     44END SUBROUTINE laplacien_rotgam
Note: See TracChangeset for help on using the changeset viewer.