Ignore:
Timestamp:
Jul 23, 2024, 7:14:34 PM (8 weeks ago)
Author:
abarral
Message:

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/bernoui.f90

    r5104 r5105  
    22! $Header$
    33
    4       SUBROUTINE bernoui (ngrid,nlay,pphi,pecin,pbern)
    5       IMPLICIT NONE
     4SUBROUTINE bernoui (ngrid,nlay,pphi,pecin,pbern)
     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    calcul de la fonction de Bernouilli aux niveaux s  .....
    15 c    phi  et  ecin  sont des arguments d'entree pour le s-pg .......
    16 c          bern       est un  argument de sortie pour le s-pg  ......
    17 c
    18 c    fonction de Bernouilli = bern = filtre de( geopotentiel +
    19 c                              energ.cinet.)
    20 c
    21 c=======================================================================
    22 c
    23 c-----------------------------------------------------------------------
    24 c   Decalrations:
    25 c   -------------
    26 c
    27       include "dimensions.h"
    28       include "paramet.h"
    29 c
    30 c   Arguments:
    31 c   ----------
    32 c
    33       INTEGER nlay,ngrid
    34       REAL pphi(ngrid*nlay),pecin(ngrid*nlay),pbern(ngrid*nlay)
    35 c
    36 c   Local:
    37 c   ------
    38 c
    39       INTEGER  ijl
    40 c
    41 c-----------------------------------------------------------------------
    42 c   calcul de Bernouilli:
    43 c   ---------------------
    44 c
    45       DO ijl = 1,ngrid*nlay
    46          pbern( ijl ) =  pphi( ijl ) + pecin( ijl )
    47       END DO
    48 c
    49 c-----------------------------------------------------------------------
    50 c   filtre:
    51 c   -------
    52 c
    53       CALL filtreg( pbern, jjp1, llm, 2,1, .TRUE., 1 )
    54 c
    55 c-----------------------------------------------------------------------
    56       RETURN
    57       END
     7  !=======================================================================
     8  !
     9  !   Auteur:   P. Le Van
     10  !   -------
     11  !
     12  !   Objet:
     13  !   ------
     14  ! calcul de la fonction de Bernouilli aux niveaux s  .....
     15  ! phi  et  ecin  sont des arguments d'entree pour le s-pg .......
     16  !      bern       est un  argument de sortie pour le s-pg  ......
     17  !
     18  !    fonction de Bernouilli = bern = filtre de( geopotentiel +
     19  !                          energ.cinet.)
     20  !
     21  !=======================================================================
     22  !
     23  !-----------------------------------------------------------------------
     24  !   Decalrations:
     25  !   -------------
     26  !
     27  include "dimensions.h"
     28  include "paramet.h"
     29  !
     30  !   Arguments:
     31  !   ----------
     32  !
     33  INTEGER :: nlay,ngrid
     34  REAL :: pphi(ngrid*nlay),pecin(ngrid*nlay),pbern(ngrid*nlay)
     35  !
     36  !   Local:
     37  !   ------
     38  !
     39  INTEGER :: ijl
     40  !
     41  !-----------------------------------------------------------------------
     42  !   calcul de Bernouilli:
     43  !   ---------------------
     44  !
     45  DO ijl = 1,ngrid*nlay
     46     pbern( ijl ) =  pphi( ijl ) + pecin( ijl )
     47  END DO
     48  !
     49  !-----------------------------------------------------------------------
     50  !   filtre:
     51  !   -------
     52  !
     53  CALL filtreg( pbern, jjp1, llm, 2,1, .TRUE., 1 )
     54  !
     55  !-----------------------------------------------------------------------
     56  RETURN
     57END SUBROUTINE bernoui
Note: See TracChangeset for help on using the changeset viewer.