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/dyn3dmem/gr_u_scal_loc.f90

    r5245 r5246  
    22! $Header$
    33!
    4       SUBROUTINE gr_u_scal_loc(nx,x_u,x_scal)
    5 c%W%    %G%
    6 c=======================================================================
    7 c
    8 c   Author:    Frederic Hourdin      original: 11/11/92
    9 c   -------
    10 c
    11 c   Subject:
    12 c   ------
    13 c
    14 c   Method:
    15 c   --------
    16 c
    17 c   Interface:
    18 c   ----------
    19 c
    20 c      Input:
    21 c      ------
    22 c
    23 c      Output:
    24 c      -------
    25 c
    26 c=======================================================================
    27       USE parallel_lmdz
    28       IMPLICIT NONE
    29 c-----------------------------------------------------------------------
    30 c   Declararations:
    31 c   ---------------
     4SUBROUTINE gr_u_scal_loc(nx,x_u,x_scal)
     5  !%W%    %G%
     6  !=======================================================================
     7  !
     8  !   Author:    Frederic Hourdin      original: 11/11/92
     9  !   -------
     10  !
     11  !   Subject:
     12  !   ------
     13  !
     14  !   Method:
     15  !   --------
     16  !
     17  !   Interface:
     18  !   ----------
     19  !
     20  !  Input:
     21  !  ------
     22  !
     23  !  Output:
     24  !  -------
     25  !
     26  !=======================================================================
     27  USE parallel_lmdz
     28  IMPLICIT NONE
     29  !-----------------------------------------------------------------------
     30  !   Declararations:
     31  !   ---------------
    3232
    33       INCLUDE "dimensions.h"
    34       INCLUDE "paramet.h"
    35       INCLUDE "comgeom.h"
     33  INCLUDE "dimensions.h"
     34  INCLUDE "paramet.h"
     35  INCLUDE "comgeom.h"
    3636
    37 c   Arguments:
    38 c   ----------
     37  !   Arguments:
     38  !   ----------
    3939
    40       INTEGER nx
    41       REAL x_u(ijb_u:ije_u,nx),x_scal(ijb_u:ije_u,nx)
     40  INTEGER :: nx
     41  REAL :: x_u(ijb_u:ije_u,nx),x_scal(ijb_u:ije_u,nx)
    4242
    43 c   Local:
    44 c   ------
     43  !   Local:
     44  !   ------
    4545
    46       INTEGER l,ij
    47       INTEGER :: ijb,ije
     46  INTEGER :: l,ij
     47  INTEGER :: ijb,ije
    4848
    49 c-----------------------------------------------------------------------
    50       ijb=ij_begin
    51       ije=ij_end
     49  !-----------------------------------------------------------------------
     50  ijb=ij_begin
     51  ije=ij_end
    5252
    53 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
    54       DO l=1,nx
    55          DO ij=ijb+1,ije
    56             x_scal(ij,l)=
    57      s      (aireu(ij)*x_u(ij,l)+aireu(ij-1)*x_u(ij-1,l))
    58      s      /(aireu(ij)+aireu(ij-1))
    59          ENDDO
    60       ENDDO
     53!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     54  DO l=1,nx
     55     DO ij=ijb+1,ije
     56        x_scal(ij,l)= &
     57              (aireu(ij)*x_u(ij,l)+aireu(ij-1)*x_u(ij-1,l)) &
     58              /(aireu(ij)+aireu(ij-1))
     59     ENDDO
     60  ENDDO
    6161!$OMP ENDDO NOWAIT
    6262
    63       ijb=ij_begin
    64       ije=ij_end
     63  ijb=ij_begin
     64  ije=ij_end
    6565
    66 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK)       
    67       DO l=1,nx
    68          DO ij=ijb,ije-iip1+1,iip1
    69            x_scal(ij,l)=x_scal(ij+iip1-1,l)
    70         ENDDO
    71       ENDDO
     66!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     67  DO l=1,nx
     68     DO ij=ijb,ije-iip1+1,iip1
     69       x_scal(ij,l)=x_scal(ij+iip1-1,l)
     70    ENDDO
     71  ENDDO
    7272!$OMP ENDDO NOWAIT
    73       RETURN
    74      
    75       END
     73  RETURN
     74
     75END SUBROUTINE gr_u_scal_loc
Note: See TracChangeset for help on using the changeset viewer.