Skip to content
Snippets Groups Projects
spawn_field2.f90 50.6 KiB
Newer Older
!MNH_LIC Copyright 1995-2019 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_FIELD2
!#######################
!
INTERFACE
!
      SUBROUTINE SPAWN_FIELD2(KXOR,KYOR,KXEND,KYEND,KDXRATIO,KDYRATIO,HTURB,   &
               PUT,PVT,PWT,PTHVT,PRT,PHUT,PTKET,PSVT,PZWS,PATC,                &
               PSRCT,PSIGS,                                                    &
               PLSUM,PLSVM,PLSWM,PLSTHM,PLSRVM,PLSZWSM,                        &
               PDTHFRC,PDRVFRC,PTHREL,PRVREL,                                  &
               PVU_FLUX_M,PVTH_FLUX_M,PWTH_FLUX_M,                             &
               KIB2,KJB2,KIE2,KJE2,                                            &
               KIB1,KJB1,KIE1,KJE1                                             )
!
INTEGER,   INTENT(IN)  :: KXOR,KXEND !  horizontal position (i,j) of the ORigin and END  
INTEGER,   INTENT(IN)  :: KYOR,KYEND ! of the model 2 domain, relative to model 1
INTEGER,   INTENT(IN)  :: KDXRATIO   !  x and y-direction Resolution ratio
INTEGER,   INTENT(IN)  :: KDYRATIO   ! between model 2 and model 1
CHARACTER (LEN=4), INTENT(IN) :: HTURB !  Kind of turbulence parameterization
!
REAL, DIMENSION(:,:,:),   INTENT(OUT) :: PUT,PVT,PWT        !  model 2
REAL, DIMENSION(:,:,:),   INTENT(OUT) :: PTKET              ! variables
REAL, DIMENSION(:,:,:,:), INTENT(OUT) :: PRT,PSVT,PATC      !   at t
REAL, DIMENSION(:,:,:),   INTENT(OUT) :: PTHVT,PHUT         !
REAL, DIMENSION(:,:),     INTENT(OUT) :: PZWS
REAL, DIMENSION(:,:,:),   INTENT(OUT) :: PSRCT,PSIGS  ! secondary
                                                            ! prognostic variables
           ! Larger Scale fields for relaxation and diffusion
REAL, DIMENSION(:,:,:),          INTENT(OUT) :: PLSUM, PLSVM, PLSWM 
REAL, DIMENSION(:,:),            INTENT(OUT) :: PLSZWSM
REAL, DIMENSION(:,:,:),          INTENT(OUT) :: PLSTHM,  PLSRVM     
REAL, DIMENSION(:,:,:,:),        INTENT(OUT) :: PDTHFRC,PDRVFRC
REAL, DIMENSION(:,:,:,:),        INTENT(OUT) :: PTHREL,PRVREL
REAL, DIMENSION(:,:,:),          INTENT(OUT) :: PVU_FLUX_M,PVTH_FLUX_M,PWTH_FLUX_M
!
           ! Arguments for spawning with 2 input files (father+son1)
TYPE(TFILEDATA),   OPTIONAL, INTENT(IN) :: TPSONFILE ! input FM-file SON
INTEGER,           OPTIONAL, INTENT(IN) :: KIUSON  ! upper dimensions of the
INTEGER,           OPTIONAL, INTENT(IN) :: KJUSON  !input FM-file SON
INTEGER,           OPTIONAL, INTENT(IN) :: KIB2,KJB2 ! indexes for common
INTEGER,           OPTIONAL, INTENT(IN) :: KIE2,KJE2 !domain in model2
INTEGER,           OPTIONAL, INTENT(IN) :: KIB1,KJB1 !and in
INTEGER,           OPTIONAL, INTENT(IN) :: KIE1,KJE1 !SON
END SUBROUTINE SPAWN_FIELD2
!
END INTERFACE
!
END MODULE MODI_SPAWN_FIELD2
!     ##########################################################################
      SUBROUTINE SPAWN_FIELD2(KXOR,KYOR,KXEND,KYEND,KDXRATIO,KDYRATIO,HTURB,   &
               PUT,PVT,PWT,PTHVT,PRT,PHUT,PTKET,PSVT, PZWS,PATC,                &
               PSRCT,PSIGS,                                                    &
               PLSUM,PLSVM,PLSWM,PLSTHM,PLSRVM,PLSZWSM,                        &
               PDTHFRC,PDRVFRC,PTHREL,PRVREL,                                  &
               PVU_FLUX_M,PVTH_FLUX_M,PWTH_FLUX_M,                             &
               KIB2,KJB2,KIE2,KJE2,                                            &
               KIB1,KJB1,KIE1,KJE1                                             )
!     ##########################################################################
!
!!****  *SPAWN_FIELD2 * - subroutine generating the model 2 prognostic and LS
!!                      fields, consistently with the spawning model 1.
!!
!!    PURPOSE
!!    -------
!!
!!      The prognostic and LS fields are interpolated from the model 1, to 
!!    initialize the model 2.
!!
!!**  METHOD
!!    ------
!!
!!      The model 2 variables are transmitted by argument (P or K prefixes),
!!    while the ones of model 1 are declared through calls to MODD_... 
!!    (X or N prefixes)
!!
!!      For the case where the resolution ratio between models is 1, 
!!    the horizontal interpolation becomes a simple equality.
!!      For the general case where resolution ratio is not egal to one,
!!    fields are interpolated using 2 types of interpolations:
!!                 1. Clark and Farley (JAS 1984) on 9 points 
!!                 2. Bikhardt on 16 points
!!
!!    EXTERNAL
!!    --------
!!      
!!      Routine BIKHARDT      : to perform horizontal interpolations
!!      Routine CLARK_FARLEY  : to perform horizontal interpolations
!!
!! 
!!    IMPLICIT ARGUMENTS
!!    ------------------ 
!!      Module MODD_PARAMETERS : contains parameters 
!!      Module MODD_CONF       : contains NVERB
!!      Module MODD_CONF1      : contains CONF_MODEL(1)%NRR (total Number of moist variables)
!!      Module MODD_FIELD1     : contains pronostic variables of model 1
!!      Module MODD_LSFIELD1   : contains LB and LS variables of model 1
!!      Module MODD_REF1       : contains RHODJ of model 1
!!      Module MODD_GRID1      : contains grid variables
!!
!!    REFERENCE
!!    ---------
!!
!!       Book1 of the documentation
!!       SUBROUTINE SPAWN_FIELD2 (Book2 of the documentation)
!!      
!!
!!    AUTHOR
!!    ------
!!
!!       J.P. Lafore     * METEO-FRANCE *
!!
!!    MODIFICATIONS
!!    -------------
!!
!!      Original    12/01/95
!!      Modification 20/03/95 (I.Mallet) change Large Scale fields initialization 
!!      Modification 27/04/95 (    "   ) remove R from the historical variables 
!!      Modification 17/04/96  (Lafore) Different resolution ratio case introduction
!!      Modification 10/06/96 (V.Masson) remove the loops in case of no resolution change
!!                                       and bug in initialization of ZBFY
!!      Modification 10/06/96 (V.Masson) interpolation computations performed in
!!                                       independant routines
!!                   10/10/96 (J. Stein) add SRCM and SRCT
!!      Modification 21/11/96 (Lafore)   move from BIKHARDT2 to BIKHARDT routine
!!      Modification 21/11/96 (Lafore)   "surfacic" LS fields
!!      Modification 10/07/97 (Masson)   remove pressure interpolations
!!      Modification 17/07/97 (Masson)   add EPS and tests on other variables
!!      Modification 14/09/97 (Masson)   interpolation of relative humidity
!!      Modification 14/09/97 (J. Stein) add the LB and LS fields
!!      Modification 27/07/98 (P. Jabouille) compute HU for all the cases
!!      Modification 01/02/01 (D.Gazen)  add module MODD_NSV for NSV variable
!!      Modification 07/07/05 (D.Barbary) spawn with 2 input files (father+son1)
!!      Modification 05/06                Remove EPS, Clark and Farley
!!      Modification 06/12  (M.Tomasini)  Interpolation of turbulent fluxes (EDDY_FLUX)
!!                                        for 2D west african monsoon
!!      Modification 07/13  (Bosseur & Filippi) Adds Forefire
!!      Modification 2014 (M.Faivre)
!!      Modification 01/15  (C. Barthe)   add LNOx
!!      Modification 25/02/2015 (M.Moge) correction of the parallelization attempted by M.Faivre
!!      Modification 15/04/2016 (P.Tulet) bug allocation ZSVT_C
!!                   29/04/2016 (J.Escobar) bug in use of ZSVT_C in SET_LSFIELD_1WAY_ll        
Gaelle TANGUY's avatar
Gaelle TANGUY committed
!!      Modification    01/2016  (JP Pinty) Add LIMA
!!  Philippe Wautelet: 05/2016-04/2018: new data structures and calls for I/O
!!      Modification 05/03/2018 (J.Escobar) bypass gridnesting special case KD(X/Y)RATIO == 1 not parallelized
!!      Bielli S. 02/2019  Sea salt : significant sea wave height influences salt emission; 5 salt modes
!  P. Wautelet 14/03/2019: correct ZWS when variable not present in file
!-------------------------------------------------------------------------------
!
!*       0.     DECLARATIONS
!               ------------
!
USE MODD_2D_FRC
USE MODD_ADVFRC_n
USE MODD_BIKHARDT_n
USE MODD_CH_AEROSOL,      ONLY: CAERONAMES
USE MODD_CH_M9_n,         ONLY: CNAMES, CICNAMES
USE MODD_CONF
USE MODD_CST
USE MODD_DUST,            ONLY: CDUSTNAMES
USE MODD_ELEC_DESCR,      ONLY: CELECNAMES
USE MODD_FIELD_n,         ONLY: FIELD_MODEL, XZWS_DEFAULT
USE MODD_PARAM_LIMA,      ONLY: NMOD_CCN, NMOD_IFN, NMOD_IMM, NINDICE_CCN_IMM,&
                                LSCAV, LAERO_MASS, LHHONI
USE MODD_PARAM_LIMA_COLD, ONLY: CLIMA_COLD_NAMES
USE MODD_PARAM_LIMA_WARM, ONLY: CLIMA_WARM_NAMES, CAERO_MASS
USE MODD_RAIN_C2R2_DESCR, ONLY: C2R2NAMES
USE MODD_RELFRC_n 
USE MODD_SALT,            ONLY: CSALTNAMES
USE MODD_SPAWN
USE MODE_FIELD,           ONLY: TFIELDDATA,TYPEREAL
USE MODE_MODELN_HANDLER
USE MODE_MPPDB
USE MODE_THERMO
USE MODE_TOOLS,           ONLY: UPCASE
Loading
Loading full blame...