Skip to content
Snippets Groups Projects
spawn_model2.f90 57.5 KiB
Newer Older
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt  
!MNH_LIC for details. version 1.
!########################
MODULE MODI_SPAWN_MODEL2
!########################
!
INTERFACE
!
      SUBROUTINE SPAWN_MODEL2 (KRR,KSV_USER,HTURB,HSURF,HCLOUD,    &
                               HCHEM_INPUT_FILE,HSPAFILE,HSPANBR,  &
                               HSONFILE,HINIFILE,HINIFILEPGD,OSPAWN_SURF       )
!
INTEGER,               INTENT(IN)  :: KRR         ! Number of moist variables
INTEGER,               INTENT(IN)  :: KSV_USER    ! Number of Users Scalar Variables
CHARACTER (LEN=4),     INTENT(IN)  :: HTURB       ! Kind of turbulence parameterization
CHARACTER (LEN=4),     INTENT(IN)  :: HSURF       ! Kind of surface parameterization
CHARACTER (LEN=4),     INTENT(IN)  :: HCLOUD      ! Kind of cloud parameterization
                                                  ! model 2 physical domain
CHARACTER (LEN=*),     INTENT(IN) :: HSPAFILE     ! possible name of the output FM-file
CHARACTER (LEN=*),     INTENT(IN) :: HSPANBR      ! NumBeR associated to the SPAwned file
CHARACTER (LEN=*),     INTENT(IN) :: HSONFILE     ! name of the input FM-file SON
CHARACTER (LEN=80),    INTENT(IN) :: HCHEM_INPUT_FILE
CHARACTER (LEN=*),     INTENT(IN) :: HINIFILE     ! Input file
CHARACTER (LEN=*),     INTENT(IN) :: HINIFILEPGD  ! Input pgd file
LOGICAL,               INTENT(IN) :: OSPAWN_SURF  ! flag to spawn surface fields
!
END SUBROUTINE SPAWN_MODEL2
!
END INTERFACE
!
END MODULE MODI_SPAWN_MODEL2
!     ######spl
      SUBROUTINE SPAWN_MODEL2 (KRR,KSV_USER,HTURB,HSURF,HCLOUD,    &
                               HCHEM_INPUT_FILE,HSPAFILE,HSPANBR,  &
                               HSONFILE,HINIFILE,HINIFILEPGD,OSPAWN_SURF       )
!     #######################################################################
!
!!****  *SPAWN_MODEL2 * - subroutine to prepare by horizontal interpolation and
!!                        write an initial FM-file spawned from an other FM-file.
!!
!!    PURPOSE
!!    -------
!!
!!      Initializes by horizontal interpolation, the model 2 in a sub-domain of 
!!    model 1,  possibly overwrites model 2 information by model SON1,
!!    and writes the resulting fields in a FM-file.
!!
!!
!!**  METHOD
!!    ------
!!
!!      In this routine, only the model 2 variables are known through the
!!    MODD_... calls.
!!
!!      The directives to perform the preparation of the initial FM
!!    file are stored in EXSPA.nam file.
!!
!!      The following  SPAWN_MODEL2 routine :
!!
!!             - sets default values of DESFM files
!!             - reads the namelists part of EXSPA file which gives the
!!      directives concerning the spawning to perform
!!             - controls the domain size of model 2 and initializes its 
!!      configuration for parameterizations and LBC
!!             - allocates memory for arrays
!!             - computes the interpolation coefficients needed to spawn model 2 
!!      2 types of interpolations are used:
!!                 1. Clark and Farley (JAS 1984) on 9 points 
!!                 2. Bikhardt on 16 points
!!             - initializes fields
!!             - reads SON1 fields and overwrites on common domain
!!             - writes the DESFM file (variables written have been initialized
!!      by reading the DESFM file concerning the model 1)
!!             - writes the LFIFM file. 
!!
!!       Finally some control prints are performed on the output listing.
!!
!!    EXTERNAL
!!    --------
!!
!!      FMATTR        : to associate a logical unit number to a file
!!      Module MODE_GRIDPROJ : contains conformal projection routines
!!           SM_GRIDPROJ   : to compute some grid variables, in
!!                           case of conformal projection.
!!      Module MODE_GRIDCART : contains cartesian geometry routines
!!           SM_GRIDCART   : to compute some grid variables, in
!!                           case of cartesian geometry.
!!      SET_REF       : to compute  rhoJ 
!!      TOTAL_DMASS   : to compute the total mass of dry air
!!      ANEL_BALANCE2  : to apply an anelastic correction in the case of changing
!!                      resolution between the two models
!!      FMOPEN        : to open a FM-file (DESFM + LFIFM)
!!      WRITE_DESFM   : to write the  DESFM file
!!      WRITE_LFIFM   : to write the  LFIFM file  
!!      FMCLOS        : to close a FM-file (DESFM + LFIFM)
!!      INI_BIKHARDT2     : initializes Bikhardt coefficients
!!
!!
!! 
!!    IMPLICIT ARGUMENTS
!!    ------------------ 
!!
!!      Module MODD_PARAMETERS : contains parameters 
!!      Module MODD_CONF       : contains configuration variables for all models
!!      Module MODD_CTURB :
!!         XTKEMIN : mimimum value for the TKE
!!      Module MODD_GRID       : contains grid variables for all models
!!      Module USE MODD_DYN    : contains configuration for the dynamics
!!      Module MODD_REF        : contains reference state variables for
!!                               all models
!!
!!      Module MODD_DIM2       : contains dimensions 
!!      Module MODD_CONF2      : contains configuration variables 
!!      Module MODD_GRID2      : contains grid variables  
!!      Module MODD_TIME2      : contains time variables and uses MODD_TIME
!!      Module MODD_REF2       : contains reference state variables 
!!      Module MODD_FIELD2     : contains prognostic variables
!!      Module MODD_LSFIELD2   : contains Larger Scale fields
!!      Module MODD_GR_FIELD2  : contains surface fields
!!      Module MODD_DYN2       : contains dynamic control variables for model 2 
!!      Module MODD_LBC2       : contains lbc control variables for model 2
!!      Module MODD_PARAM2     : contains configuration for physical parameterizations
!!
!!    REFERENCE
!!    ---------
!!
!!       PROGRAM SPAWN_MODEL2 (Book2 of the documentation)
!!      
!!
!!    AUTHOR
!!    ------
!!
!!       J.P. Lafore     * METEO-FRANCE *
!!
!!    MODIFICATIONS
!!    -------------
!!
!!      Original     11/01/95 
!!      Modification 27/04/95  (I.Mallet) remove R from the historical variables
!!      Modification 16/04/96  (Lafore) Different resolution ratio case introduction
!!      Modification 24/04/96  (Lafore & Masson) Initialization of LUSERWs
!!      Modification 24/04/96  (Masson) Correction of positivity on Rw and TKE
!!      Modification 25/04/96  (Masson) Copies of internal zs on external points
!!      Modification 02/05/96  (Stein Jabouille) initialize CCONF
!!      Modification 31/05/96  (Lafore) Cumputing time analysis
!!      Modification 10/06/96  (Masson) Call to anel_balance in all cases
!!      Modification 10/06/96  (Masson) Bikhardt and Clark_and_Farley coefficients
!!                                      incorporated in modules
!!      Modification 12/06/96  (Masson) default values of NJMAX and KDYRATIO
!!                                      if 2D version of the model
!!      Modification 13/06/96  (Masson) choice of the name of the spawned file
!!      Modification 30/07/96  (Lafore) MY_NAME and DAD_NAME writing for nesting
!!      Modification 25/09/96  (Masson) grid optionnaly given by a fm file
!!                                      and number of points given relatively
!!                                      to model 1
!!      Modification 10/10/96  (Masson) L1D and L2D verifications
!!      Modification 12/11/96  (Masson) allocations of XSRCM and XSRCT
!!      Modification 19/11/96  (Masson) add deep convection
!!      Modification 26/11/96  (Lafore) spawning configuration writing on the FM-file
!!      Modification 26/11/96  (Lafore) replacing of TOTAL_DMASS by REAL_DMASS
!!      Modification 27/02/97  (Lafore) "surfacic" LS fields
!!      Modification 10/04/97  (Lafore) proper treatment of minima
!!      Modification 09/07/97  (Masson) absolute pressure and directional z0
!!      Modification 10/07/97  (Masson) routines SPAWN_PRESSURE2 and DRY_MASS
!!      Modification 17/07/97  (Masson) vertical interpolations and EPS
!!      Modification 29/07/97  (Masson) split mode_lfifm_pgd
!!      Modification 10/08/97  (Lafore) initialization of LUSERV
!!      Modification 14/09/97  (Masson) use of relative humidity
!!      Modification 08/12/97  (Masson) deallocation of model 1 variables
!!      Modification 24/12/97  (Masson) directional z0 parameters and orographies
!!      Modification 20/07/98  (Stein ) add the LB fields
!!      Modification 15/03/99  (Masson) cover types
!!      Modification 15/07/99  (Jabouille) shift domain initialization in INI_SIZE_SPAWN
!!      Modification 04/01/00  (Masson) removes TSZ0 option
!!      Modification 29/11/02  (Pinty)  add C3R5, ICE2, ICE4
!!      Modification 07/07/05  (D.Barbary) spawn with 2 input files (father+son1)
!!      Modification 20/05/06  Remove EPS, Clark and Farley interpolation
!!                             Replace DRY_MASS by TOTAL_DMASS
!!      Modification 06/12  (M.Tomasini) Interpolation of the advective forcing (ADVFRC)
!!                                       and of the turbulent fluxes (EDDY_FLUX)
!!      Modification 07/13  (Bosseur & Filippi) Adds Forefire
!!                   24/04/2014 (J.escobar) bypass CRAY internal compiler error on IIJ computation
!!      Modification 06/2014   (C.Lac) Initialization of physical param of
!!                                      model2 before the call to ini_nsv
!!      Modification 05/02/2015 (M.Moge) parallelization of SPAWNING
!!      J.Escobar : 15/09/2015 : WENO5 & JPHEXT <> 1 
!!      J.Escobar   02/05/2016 : test ZZS_MAX in // 
!-------------------------------------------------------------------------------
!
!*       0.     DECLARATIONS
!               ------------
!
USE MODD_PARAMETERS       ! Declarative modules
USE MODD_CST
USE MODD_CONF
USE MODD_CTURB
USE MODD_GRID 
USE MODD_REF
USE MODD_DYN
USE MODD_NESTING
USE MODD_SPAWN
USE MODD_NSV
USE MODD_PASPOL
!
USE MODD_DIM_n
USE MODD_DYN_n
USE MODD_CONF_n 
USE MODD_LBC_n
USE MODD_GRID_n
USE MODD_TIME_n
USE MODD_REF_n
USE MODD_FIELD_n
USE MODD_LSFIELD_n
USE MODD_DUMMY_GR_FIELD_n
USE MODD_PRECIP_n
USE MODD_ELEC_n
USE MODD_LUNIT_n
USE MODD_PARAM_n
USE MODD_TURB_n
USE MODD_METRICS_n
USE MODD_CH_MNHC_n
USE MODD_PASPOL_n
!$20140515
USE MODD_VAR_ll, ONLY : NPROC
!USE MODD_IO_ll, ONLY : ISP,GSMONOPROC
!
USE MODE_GRIDCART         ! Executive modules
USE MODE_GRIDPROJ
USE MODE_ll
!
USE MODI_READ_HGRID
USE MODI_SPAWN_GRID2  
USE MODI_SPAWN_FIELD2
USE MODI_SPAWN_SURF
USE MODI_VER_INTERP_FIELD
USE MODI_SPAWN_PRESSURE2
USE MODI_SPAWN_SURF2_RAIN
USE MODI_SET_REF
USE MODI_TOTAL_DMASS
USE MODI_ANEL_BALANCE_n
USE MODI_WRITE_DESFM_n
USE MODI_WRITE_LFIFM_n
USE MODI_METRICS
USE MODI_INI_BIKHARDT_n
USE MODI_DEALLOCATE_MODEL1
USE MODI_BOUNDARIES
USE MODI_INI_NSV
USE MODI_CH_INIT_SCHEME_n
!$20140710
USE MODI_UPDATE_METRICS
!
USE MODE_FM
USE MODE_IO_ll
USE MODE_MODELN_HANDLER
USE MODE_FMREAD
!
USE MODE_THERMO
!
USE MODI_SECOND_MNH
!
#ifdef MNH_NCWRIT
USE MODN_NCOUT
USE MODE_UTIL
#endif
! Modules for  EDDY_FLUX
USE MODD_LATZ_EDFLX
USE MODD_DEF_EDDY_FLUX_n           
USE MODD_DEF_EDDYUV_FLUX_n
USE MODD_ADVFRC_n
USE MODD_RELFRC_n
USE MODD_2D_FRC
!
!USE MODE_LB_ll, ONLY : SET_LB_FIELD_ll
USE MODI_GET_SIZEX_LB
USE MODI_GET_SIZEY_LB
!
USE MODD_MPIF
USE MODD_VAR_ll
!
IMPLICIT NONE
!
!*       0.1.1  Declarations of global variables not declared in the modules :
!
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZJ ! Jacobian
!
!
!*       0.1.2  Declarations of dummy arguments :
!
INTEGER,               INTENT(IN)  :: KRR         ! Number of moist variables
INTEGER,               INTENT(IN)  :: KSV_USER    ! Number of Users Scalar Variables
CHARACTER (LEN=4),     INTENT(IN)  :: HTURB       ! Kind of turbulence parameterization
CHARACTER (LEN=4),     INTENT(IN)  :: HSURF       ! Kind of surface parameterization
CHARACTER (LEN=4),     INTENT(IN)  :: HCLOUD      ! Kind of cloud parameterization
CHARACTER (LEN=*),     INTENT(IN) :: HSPAFILE     ! possible name of the output FM-file
CHARACTER (LEN=*),     INTENT(IN) :: HSPANBR      ! NumBeR associated to the SPAwned file
CHARACTER (LEN=*),     INTENT(IN) :: HSONFILE     ! name of the input FM-file SON
CHARACTER (LEN=80),    INTENT(IN) :: HCHEM_INPUT_FILE
CHARACTER (LEN=*),     INTENT(IN) :: HINIFILE     ! Input file
CHARACTER (LEN=*),     INTENT(IN) :: HINIFILEPGD  ! Input pgd file
LOGICAL,               INTENT(IN) :: OSPAWN_SURF  ! flag to spawn surface fields
!
!*       0.1.3  Declarations of local variables :
!
!
INTEGER :: IRESP    ! Return codes in FM routines
INTEGER :: ILUOUT   ! Logical unit number for the output listing 
INTEGER :: INPRAR   ! Number of articles predicted in the LFIFM file
INTEGER :: ININAR   ! Number of articles present in the LFIFM file
INTEGER :: ITYPE    ! Type of file (cpio or not)
INTEGER             :: IGRID,ILENCH   !   File management
CHARACTER (LEN=100) :: YCOMMENT       ! variables
!
CHARACTER (LEN=32) :: YDESFM          ! Name of the desfm part of the FM-file
!  
!
INTEGER             :: IIU            ! Upper dimension in x direction
INTEGER             :: IJU            ! Upper dimension in y direction
INTEGER             :: IKU            ! Upper dimension in z direction
INTEGER             :: IIB            ! indice I Beginning in x direction
INTEGER             :: IJB            ! indice J Beginning in y direction
INTEGER             :: IKB            ! indice K Beginning in z direction
INTEGER             :: IIE            ! indice I End       in x direction 
INTEGER             :: IJE            ! indice J End       in y direction 
INTEGER             :: IKE            ! indice K End       in z direction 
INTEGER             :: JK             ! Loop index in z direction 
INTEGER             :: JLOOP,JKLOOP   ! Loop indexes 
INTEGER             :: JSV            ! loop index for scalar variables
INTEGER             :: JRR            ! loop index for moist variables
!
REAL, DIMENSION(:,:),   ALLOCATABLE :: ZZS_LS ! large scale interpolated zs
REAL, DIMENSION(:,:),   ALLOCATABLE :: ZZSMT_LS ! large scale interpolated smooth zs
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZZZ_LS ! large scale interpolated z
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZTHVT  ! virtual potential temperature
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZHUT   ! relative humidity
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZSUMRT ! sum of water ratios
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZRHOD  ! dry density
!
REAL    :: ZTIME1,ZTIME2,ZSTART,ZEND,ZTOT,ZALL,ZPERCALL ! for computing time analysis
REAL    ::     ZGRID2,    ZSURF2,    ZFIELD2,     ZVER, &
           ZPRESSURE2,    ZANEL,      ZWRITE,     ZMISC
REAL    :: ZPERCGRID2,ZPERCSURF2,ZPERCFIELD2, ZPERCVER, &
       ZPERCPRESSURE2, ZPERCANEL, ZPERCWRITE,ZPERCMISC
!
INTEGER, DIMENSION(2) :: IIJ
INTEGER               :: IK4000
INTEGER               :: IMI ! Old Model index
!
! Spawning variables for the SON 1 (input one)
INTEGER             :: IIMAXSON,IJMAXSON ! physical dimensions
INTEGER             :: IIUSON,IJUSON     ! upper dimensions
INTEGER             :: IXSIZESON,IYSIZESON ! sizes according to model1 grid
INTEGER             :: IDXRATIOSON,IDYRATIOSON ! x and y-resolution ratios
INTEGER             :: IXORSON,IYORSON   ! horizontal position 
INTEGER             :: IXENDSON,IYENDSON !in x and y directions
! Common indexes for the SON 2 (output one, model2)
INTEGER             :: IIB2           ! indice I Beginning in x direction
INTEGER             :: IJB2           ! indice J Beginning in y direction
INTEGER             :: IIE2           ! indice I End       in x direction
INTEGER             :: IJE2           ! indice J End       in y direction
! Common indexes for the SON 1 (input one)
INTEGER             :: IIB1           ! indice I Beginning in x direction
INTEGER             :: IJB1           ! indice J Beginning in y direction
INTEGER             :: IIE1           ! indice I End       in x direction
INTEGER             :: IJE1           ! indice J End       in y direction
! Logical for no common domain between the 2 sons or no input son
LOGICAL             :: GNOSON = .TRUE.
REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZWORK3D ! working array
CHARACTER(LEN=28)   :: YDAD_SON
!$
INTEGER             :: IDIMX, IDIMY
INTEGER             :: IINFO_ll
TYPE(LIST_ll), POINTER :: TZFIELDS_ll=>NULL()   ! list of fields to exchange
INTEGER             :: NXOR_TMP, NYOR_TMP, NXEND_TMP, NYEND_TMP 
INTEGER :: IISIZEXF,IJSIZEXF,IISIZEXFU,IJSIZEXFU     ! dimensions of the
INTEGER :: IISIZEX4,IJSIZEX4,IISIZEX2,IJSIZEX2       ! West-east LB arrays
INTEGER :: IISIZEYF,IJSIZEYF,IISIZEYFV,IJSIZEYFV     ! dimensions of the
INTEGER :: IISIZEY4,IJSIZEY4,IISIZEY2,IJSIZEY2       ! 
Loading
Loading full blame...