Ignore:
Timestamp:
Mar 5, 2014, 2:19:12 PM (11 years ago)
Author:
lguez
Message:

Converted to free source form files in libf/phylmd which were still in
fixed source form. The conversion was done using the polish mode of
the NAG Fortran Compiler.

In addition to converting to free source form, the processing of the
files also:

-- indented the code (including comments);

-- set Fortran keywords to uppercase, and set all other identifiers
to lower case;

-- added qualifiers to end statements (for example "end subroutine
conflx", instead of "end");

-- changed the terminating statements of all DO loops so that each
loop ends with an ENDDO statement (instead of a labeled continue).

-- replaced #include by include.

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/ini_wake.F90

    r1988 r1992  
    1 !
     1
    22! $Id$
    3 !
    4       SUBROUTINE INI_WAKE(wape,fip,it_wape_prescr,
    5      :     wape_prescr, fip_prescr, alp_bl_prescr, ale_bl_prescr)
    6 ***************************************************************
    7 *                                                             *
    8 *        INI_WAKE : variables d'initialisation de la poche    *
    9 *                   froide, necessaires au declenchement      *
    10 *                   de la convection.                         *
    11 *                                                             *
    12 *                                                             *
    13 ***************************************************************
    14 c Arguments
    15 c =========
    16 c Input
    17 c -----
    18 c   wape           : valeur de l'energie potentielle de la poche (WAPE)
    19 c                    dans l'etat initial
    20 c   fip            : valeur de la puissance incidente sur le front (FIP)
    21 c                    dans l'etat initial
    22 c Output
    23 c ------
    24 c   it_wape_prescr : nombre de pas de temps pendant lesquels la WAPE
    25 c            doit etre imposee.
    26 c   wape_prescr    : valeur prescrite de la WAPE.
    27 c   fip_prescr     : valeur prescrite de la FIP.
    28 c   ale_bl_prescr  : valeur prescrite de la Ale de PBL.
    29 c   alp_bl_prescr  : valeur prescrite de la Alp de PBL.
    30 c
    31 c Variables internes
    32 c ==================
    33 c   it = nbre de pas de temps lu
    34 c   w  = WAPE lue
    35 c   f  = FIP lue
    36 c   alebl  = Ale de PBL lue
    37 c   alpbl  = Alp de PBL lue
    38 c
    39       include 'iniprint.h'
    40 cdeclarations
    41       real ale_bl_prescr
    42       real alp_bl_prescr
    43       real it
    443
    45 ! FH A mettre si besoin dans physiq.def
    46 ! FH : voir avec JYG
    47       it=0.
    48       w=4.
    49       f=0.1
    50       alebl=4.
    51       alpbl=0.1
    52 c
    53 cCR: on rajoute ale et alp de la PBL precrits
    54       open (99,file='ini_wake_param.data',form='formatted',
    55      s      status='old',err=902)
    56       read (99,*) it
    57       read (99,*) w
    58       read (99,*) f
    59       read (99,*,end=901) alebl
    60       read (99,*,end=901) alpbl
    61 901   close (99)
    62 902   continue
    63 c
    64       write(lunout,*)' it,wape ',it,wape
    65       it_wape_prescr = it
    66       if (w .lt. 0) then
    67          wape_prescr = wape
    68          fip_prescr = fip
    69       else
    70          wape_prescr = w
    71          fip_prescr = f
    72       endif
    73 c
    74       write(lunout,*)' alebl, alpbl ',alebl,alpbl
    75       ale_bl_prescr=alebl
    76       alp_bl_prescr=alpbl
    77       print *,'Initialisation de la poche : WAPE, FIP imposees ='
    78      $               ,wape_prescr, fip_prescr
    79       print *, '                   pendant ',it_wape_prescr,' steps'
    80 c
    81       print *,'Initialisation de la BL: ALP, ALE imposees ='
    82      $               ,alp_bl_prescr, ale_bl_prescr
    83       return
    84       end
     4SUBROUTINE ini_wake(wape, fip, it_wape_prescr, wape_prescr, fip_prescr, &
     5    alp_bl_prescr, ale_bl_prescr)
     6  ! **************************************************************
     7  ! *
     8  ! INI_WAKE : variables d'initialisation de la poche    *
     9  ! froide, necessaires au declenchement      *
     10  ! de la convection.                         *
     11  ! *
     12  ! *
     13  ! **************************************************************
     14  ! Arguments
     15  ! =========
     16  ! Input
     17  ! -----
     18  ! wape           : valeur de l'energie potentielle de la poche (WAPE)
     19  ! dans l'etat initial
     20  ! fip            : valeur de la puissance incidente sur le front (FIP)
     21  ! dans l'etat initial
     22  ! Output
     23  ! ------
     24  ! it_wape_prescr : nombre de pas de temps pendant lesquels la WAPE
     25  ! doit etre imposee.
     26  ! wape_prescr    : valeur prescrite de la WAPE.
     27  ! fip_prescr     : valeur prescrite de la FIP.
     28  ! ale_bl_prescr  : valeur prescrite de la Ale de PBL.
     29  ! alp_bl_prescr  : valeur prescrite de la Alp de PBL.
     30
     31  ! Variables internes
     32  ! ==================
     33  ! it = nbre de pas de temps lu
     34  ! w  = WAPE lue
     35  ! f  = FIP lue
     36  ! alebl  = Ale de PBL lue
     37  ! alpbl  = Alp de PBL lue
     38
     39  include 'iniprint.h'
     40  ! declarations
     41  REAL ale_bl_prescr
     42  REAL alp_bl_prescr
     43  REAL it
     44
     45  ! FH A mettre si besoin dans physiq.def
     46  ! FH : voir avec JYG
     47  it = 0.
     48  w = 4.
     49  f = 0.1
     50  alebl = 4.
     51  alpbl = 0.1
     52
     53  ! CR: on rajoute ale et alp de la PBL precrits
     54  OPEN (99, FILE='ini_wake_param.data', FORM='formatted', STATUS='old', &
     55    ERR=902)
     56  READ (99, *) it
     57  READ (99, *) w
     58  READ (99, *) f
     59  READ (99, *, END=901) alebl
     60  READ (99, *, END=901) alpbl
     61901 CLOSE (99)
     62902 CONTINUE
     63
     64  WRITE (lunout, *) ' it,wape ', it, wape
     65  it_wape_prescr = it
     66  IF (w<0) THEN
     67    wape_prescr = wape
     68    fip_prescr = fip
     69  ELSE
     70    wape_prescr = w
     71    fip_prescr = f
     72  END IF
     73
     74  WRITE (lunout, *) ' alebl, alpbl ', alebl, alpbl
     75  ale_bl_prescr = alebl
     76  alp_bl_prescr = alpbl
     77  PRINT *, 'Initialisation de la poche : WAPE, FIP imposees =', wape_prescr, &
     78    fip_prescr
     79  PRINT *, '                   pendant ', it_wape_prescr, ' steps'
     80
     81  PRINT *, 'Initialisation de la BL: ALP, ALE imposees =', alp_bl_prescr, &
     82    ale_bl_prescr
     83  RETURN
     84END SUBROUTINE ini_wake
Note: See TracChangeset for help on using the changeset viewer.