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/geopot.f90

    r5245 r5246  
    22! $Header$
    33!
    4       SUBROUTINE geopot (ngrid, teta, pk, pks, phis, phi )
    5       IMPLICIT NONE
     4SUBROUTINE geopot (ngrid, teta, pk, pks, phis, phi )
     5  IMPLICIT NONE
    66
    7 c=======================================================================
    8 c
    9 c   Auteur:  P. Le Van
    10 c   -------
    11 c
    12 c   Objet:
    13 c   ------
    14 c
    15 c    *******************************************************************
    16 c    ....   calcul du geopotentiel aux milieux des couches    .....
    17 c    *******************************************************************
    18 c
    19 c    ....   l'integration se fait de bas en haut  ....
    20 c
    21 c    .. ngrid,teta,pk,pks,phis sont des argum. d'entree pour le s-pg ..
    22 c              phi               est un  argum. de sortie pour le s-pg .
    23 c
    24 c=======================================================================
    25 c-----------------------------------------------------------------------
    26 c   Declarations:
    27 c   -------------
     7  !=======================================================================
     8  !
     9  !   Auteur:  P. Le Van
     10  !   -------
     11  !
     12  !   Objet:
     13  !   ------
     14  !
     15  !    *******************************************************************
     16  !    ....   calcul du geopotentiel aux milieux des couches    .....
     17  !    *******************************************************************
     18  !
     19  ! ....   l'integration se fait de bas en haut  ....
     20  !
     21  ! .. ngrid,teta,pk,pks,phis sont des argum. d'entree pour le s-pg ..
     22  !          phi               est un  argum. de sortie pour le s-pg .
     23  !
     24  !=======================================================================
     25  !-----------------------------------------------------------------------
     26  !   Declarations:
     27  !   -------------
    2828
    29       include "dimensions.h"
    30       include "paramet.h"
     29  include "dimensions.h"
     30  include "paramet.h"
    3131
    32 c   Arguments:
    33 c   ----------
     32  !   Arguments:
     33  !   ----------
    3434
    35       INTEGER ngrid
    36       REAL teta(ngrid,llm),pks(ngrid),phis(ngrid),pk(ngrid,llm) ,
    37      *       phi(ngrid,llm)
     35  INTEGER :: ngrid
     36  REAL :: teta(ngrid,llm),pks(ngrid),phis(ngrid),pk(ngrid,llm) , &
     37        phi(ngrid,llm)
    3838
    3939
    40 c   Local:
    41 c   ------
     40  !   Local:
     41  !   ------
    4242
    43       INTEGER l, ij
     43  INTEGER :: l, ij
    4444
    4545
    46 c-----------------------------------------------------------------------
    47 c    calcul de phi au niveau 1 pres du sol  .....
     46  !-----------------------------------------------------------------------
     47  ! calcul de phi au niveau 1 pres du sol  .....
    4848
    49       DO   1  ij  = 1, ngrid
    50       phi( ij,1 ) = phis( ij ) + teta(ij,1) * ( pks(ij) - pk(ij,1) )
    51    1  CONTINUE
     49  DO  ij  = 1, ngrid
     50  phi( ij,1 ) = phis( ij ) + teta(ij,1) * ( pks(ij) - pk(ij,1) )
     51  END DO
    5252
    53 c    calcul de phi aux niveaux superieurs  .......
     53  ! calcul de phi aux niveaux superieurs  .......
    5454
    55       DO  l = 2,llm
    56         DO  ij    = 1,ngrid
    57         phi(ij,l) = phi(ij,l-1) + 0.5 * ( teta(ij,l)  + teta(ij,l-1) )
    58      *                              *   (  pk(ij,l-1) -  pk(ij,l)    )
    59         ENDDO
    60       ENDDO
     55  DO  l = 2,llm
     56    DO  ij    = 1,ngrid
     57    phi(ij,l) = phi(ij,l-1) + 0.5 * ( teta(ij,l)  + teta(ij,l-1) ) &
     58          *   (  pk(ij,l-1) -  pk(ij,l)    )
     59    ENDDO
     60  ENDDO
    6161
    62       RETURN
    63       END
     62  RETURN
     63END SUBROUTINE geopot
Note: See TracChangeset for help on using the changeset viewer.