Ignore:
Timestamp:
Sep 7, 2012, 2:49:58 PM (12 years ago)
Author:
emillour
Message:

Common dynamics: updates to keep up with LMDZ5 Earth (rev 1649)
See file "DOC/chantiers/commit_importants.log" for details.
EM

File:
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/iniconst.F90

    r775 r776  
    11!
    2 ! $Id: iniconst.F 1520 2011-05-23 11:37:09Z emillour $
     2! $Id: iniconst.F90 1625 2012-05-09 13:14:48Z lguez $
    33!
    4       SUBROUTINE iniconst
     4SUBROUTINE iniconst
    55
    6       USE control_mod
     6  USE control_mod
    77#ifdef CPP_IOIPSL
    8       use IOIPSL
     8  use IOIPSL
    99#else
    10 ! if not using IOIPSL, we still need to use (a local version of) getin
    11       use ioipsl_getincom
     10  ! if not using IOIPSL, we still need to use (a local version of) getin
     11  use ioipsl_getincom
    1212#endif
    1313
    14       IMPLICIT NONE
    15 c
    16 c      P. Le Van
    17 c
    18 c-----------------------------------------------------------------------
    19 c   Declarations:
    20 c   -------------
    21 c
    22 #include "dimensions.h"
    23 #include "paramet.h"
    24 #include "comconst.h"
    25 #include "temps.h"
    26 #include "comvert.h"
    27 #include "iniprint.h"
     14  IMPLICIT NONE
     15  !
     16  !      P. Le Van
     17  !
     18  !   Declarations:
     19  !   -------------
     20  !
     21  include "dimensions.h"
     22  include "paramet.h"
     23  include "comconst.h"
     24  include "temps.h"
     25  include "comvert.h"
     26  include "iniprint.h"
    2827
     28  character(len=*),parameter :: modname="iniconst"
     29  character(len=80) :: abort_message
     30  !
     31  !
     32  !
     33  !-----------------------------------------------------------------------
     34  !   dimension des boucles:
     35  !   ----------------------
    2936
    30       character(len=*),parameter :: modname="iniconst"
    31       character(len=80) :: abort_message
    32 c
    33 c
    34 c
    35 c-----------------------------------------------------------------------
    36 c   dimension des boucles:
    37 c   ----------------------
     37  im      = iim
     38  jm      = jjm
     39  lllm    = llm
     40  imp1    = iim
     41  jmp1    = jjm + 1
     42  lllmm1  = llm - 1
     43  lllmp1  = llm + 1
    3844
    39       im      = iim
    40       jm      = jjm
    41       lllm    = llm
    42       imp1    = iim
    43       jmp1    = jjm + 1
    44       lllmm1  = llm - 1
    45       lllmp1  = llm + 1
     45  !-----------------------------------------------------------------------
    4646
    47 c-----------------------------------------------------------------------
     47  dtphys  = iphysiq * dtvr
     48  unsim   = 1./iim
     49  pi      = 2.*ASIN( 1. )
    4850
    49       dtphys  = iphysiq * dtvr
    50       unsim   = 1./iim
    51       pi      = 2.*ASIN( 1. )
     51  !-----------------------------------------------------------------------
     52  !
    5253
    53 c-----------------------------------------------------------------------
    54 c
     54  r       = cpp * kappa
    5555
    56       r       = cpp * kappa
     56  write(lunout,*) trim(modname),': R  CP  Kappa ',r,cpp,kappa
     57  !
     58  !-----------------------------------------------------------------------
    5759
    58       write(lunout,*) trim(modname),': R  CP  Kappa ',r,cpp,kappa
    59 c
    60 c-----------------------------------------------------------------------
     60  ! vertical discretization: default behavior depends on planet_type flag
     61  if (planet_type=="earth") then
     62     disvert_type=1
     63  else
     64     disvert_type=2
     65  endif
     66  ! but user can also specify using one or the other in run.def:
     67  call getin('disvert_type',disvert_type)
     68  write(lunout,*) trim(modname),': disvert_type=',disvert_type
    6169
    62 ! vertical discretization: default behavior depends on planet_type flag
    63       if (planet_type=="earth") then
    64         disvert_type=1
    65       else
    66         disvert_type=2
    67       endif
    68       ! but user can also specify using one or the other in run.def:
    69       call getin('disvert_type',disvert_type)
    70       write(lunout,*) trim(modname),': disvert_type=',disvert_type
    71      
    72       if (disvert_type==1) then
    73        ! standard case for Earth (automatic generation of levels)
    74        call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig,
    75      &              scaleheight)
    76       else if (disvert_type==2) then
    77         ! standard case for planets (levels generated using z2sig.def file)
    78         call disvert_noterre
    79       else
    80         write(abort_message,*) "Wrong value for disvert_type: ",
    81      &                        disvert_type
    82         call abort_gcm(modname,abort_message,0)
    83       endif
     70  pressure_exner = disvert_type == 1 ! default value
     71  call getin('pressure_exner', pressure_exner)
    8472
    85       END
     73  if (disvert_type==1) then
     74     ! standard case for Earth (automatic generation of levels)
     75     call disvert(pa,preff,ap,bp,dpres,presnivs,nivsigs,nivsig, scaleheight)
     76  else if (disvert_type==2) then
     77     ! standard case for planets (levels generated using z2sig.def file)
     78     call disvert_noterre
     79  else
     80     write(abort_message,*) "Wrong value for disvert_type: ", disvert_type
     81     call abort_gcm(modname,abort_message,0)
     82  endif
     83
     84END SUBROUTINE iniconst
Note: See TracChangeset for help on using the changeset viewer.