Skip to content
Snippets Groups Projects
prep_ideal_case.f90 66.7 KiB
Newer Older
!MNH_LIC Copyright 1994-2013 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 LICENCE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt  
!MNH_LIC for details. version 1.
!-----------------------------------------------------------------
!--------------- special set of characters for RCS information
!-----------------------------------------------------------------
! $Source$ $Revision$
! masdev4_7 BUG1 2007/06/15 17:47:18
!-----------------------------------------------------------------
!     #######################
      PROGRAM PREP_IDEAL_CASE
!     #######################
!
!!****  *PREP_IDEAL_CASE* - program to write an initial FM-file 
!!
!!    PURPOSE
!!    -------
!       The purpose of this program is to prepare an initial meso-NH file
!     (LFIFM and DESFM files) filled with some idealized fields.    
!
!      ---- The present version can provide two types of fields:
!
!      1) CIDEAL = 'CSTN' : 3D fields derived  from a vertical profile with
!         ---------------   n levels of constant moist Brunt Vaisala frequency
!             The vertical profile is read in EXPRE file.                 
!             These fields can be used for model runs 
!
!      2) CIDEAL = 'RSOU' : 3D fields derived from a radiosounding.
!          --------------- 
!             The radiosounding is read in EXPRE file. 
!             The following kind of data  is permitted :
!                  YKIND = 'STANDARD'  :   Zsol, Psol, Tsol, TDsol
!                                         (Pressure, dd, ff) , 
!                                         (Pressure, T, Td)
!                  YKIND = 'PUVTHVMR'  : zsol, Psol, Thvsol, Rsol
!                                        (Pressure, U, V) , 
!                                        (Pressure, THv, R)
!                  YKIND = 'PUVTHVHU'  :  zsol, Psol, Thvsol, Husol
!                                         (Pressure, U, V) , 
!                                         (Pressure, THv, Hu)
!                  YKIND = 'ZUVTHVHU'  :  zsol, Psol, Thvsol, Husol
!                                         (height, U, V) , 
!                                         (height, THv, Hu)
!                  YKIND = 'ZUVTHVMR'  :  zsol, Psol, Thvsol, Rsol
!                                         (height, U, V) , 
!                                         (height, THv, R)
!                  YKIND = 'PUVTHDMR'  : zsol, Psol, Thdsol, Rsol
!                                         (Pressure, U, V) , 
!                                         (Pressure, THd, R)
!                  YKIND = 'PUVTHDHU'  : zsol, Psol, Thdsol, Husol
!                                         (Pressure, U, V) , 
!                                         (Pressure, THd, Hu)
!                  YKIND = 'ZUVTHDMR'  :  zsol, Psol, Thdsol, Rsol
!                                         (height, U, V) , 
!                                         (height, THd, R)
!                  YKIND = 'ZUVTHLMR'  :  zsol, Psol, Thdsol, Rsol
!                                         (height, U, V) , 
!                                         (height, THl, Rt)
!
!             These fields can be used for model runs 
!
!      Cases (1) and (2) can be balanced
!      (geostrophic, hydrostatic  and anelastic balances) if desired.
!
!      ---- The orography can be flat (YZS='FLAT'), but also 
!      sine-shaped (YZS='SINE') or  bell-shaped (YZS='BELL')
!
!      ---- The U(z)  profile given in the RSOU and CSTN cases can
!      be multiplied (CUFUN="Y*Z") by a function of y (function FUNUY)  
!      The V(z) profile  given in the RSOU and CSTN cases can
!      be multiplied (CVFUN="X*Z") by a function of x (function FUNVX). 
!      If it is not the case, i.e. U(y,z)=U(z) then CUFUN="ZZZ" and 
!      CVFUN="ZZZ" for V(y,z)=V(z). Instead of these separable forms,
!      non-separables functions FUNUYZ (CUFUN="Y,Z")  and FUNVXZ (CVFUN="X,Z") 
!      can be used to specify the wind components.
!
!!**  METHOD
!!    ------
!!      The directives and data to perform the preparation of the initial FM
!!    file are stored in EXPRE file. This file is composed  of two parts : 
!!          - a namelists-format  part which is present in all cases
!!          - a free-format  part which contains data in cases 
!!       of discretised orography (CZS='DATA')
!!       of radiosounding (CIDEAL='RSOU') or Nv=cste  profile (CIDEAL='CSTN')
!!       of forced version (LFORCING=.TRUE.)
!!    
!!
!!      The following  PREP_IDEAL_CASE program  :
!!
!!             - initializes physical constants by calling INI_CST 
!!
!!             - sets default values for global variables which will be 
!!     written  in DESFM file and for variables in EXPRE file (namelists part)
!!     which will be written in LFIFM file.    
!!
!!             - reads the namelists part of EXPRE file which gives 
!!     informations about the preinitialization to perform,
!!
!!             - allocates memory for arrays, 
!!
!!             - initializes fields depending on the 
!!              directives  (CIDEAL in namelist NAM_CONF_PRE) :
!!  
!!                * grid variables : 
!!                  The gridpoints are regularly spaced by XDELTAX, XDELTAY.
!!               The grid is stretched along the z direction, the mesh varies 
!!               from XDZGRD near the ground to XDZTOP near the top and the 
!!               weigthing function is a TANH function characterized by its 
!!               center and width above and under this center
!!                  The orography is initialized following the kind of orography
!!               (YZS in namelist NAM_CONF_PRE) and the degrees of freedom :
!!                     sine-shape ---> ZHMAX, IEXPX,IEXPY
!!                     bell-shape ---> ZHMAX, ZAX,ZAY,IIZS,IJZS
!!                  The horizontal grid variables are initialized following
!!                the kind of geometry (LCARTESIAN in namelist NAM_CONF_PRE) 
!!                and the grid parameters XLAT0,XLON0,XBETA in both geometries
!!                and XRPK,XLONORI,XLATORI  in conformal projection.
!!                  In the  case of initialization from a radiosounding, the
!!                date and time is read in free-part of the EXPRE file. In other
!!                cases year, month and day are set to NUNDEF and time to 0.
!!
!!               * prognostic fields : 
!!
!!                     U,V,W, Theta and r. are first determined. They are
!!                multiplied by rhoj after the anelastic reference state 
!!                computation.
!!                     For the CSTN and RSOU cases, the determination of 
!!                Theta and rv is performed  respectively by SET_RSOU
!!                and by SET_CSTN which call the common routine SET_MASS. 
!!                These three routines have  the following actions :
!!          ---   The input vertical profile   is converted in 
!!                variables (U,V,thetav,r) and  interpolated
!!                on a mixed grid (with VERT_COORD) as in PREP_REAL_CASE 
!!          ---   A variation of the u-wind component( x-model axis component) 
!!                 is possible in y direction, a variation of the v-wind component 
!!                (y-model axis component) is possible in x direction.
!!          ---   Thetav could be computed with thermal wind balance
!!                (LGEOSBAL=.TRUE. with call of SET_GEOSBAL)                 
!!          ---   The mass fields (theta and r ) and the wind components are 
!!                then interpolated on the model grid with orography  as in
!!                PREP_REAL_CASE with the option LSHIFT                
!!          ---   An  anelastic correction is  applied in PRESSURE_IN_PREP in
!!                the case of non-vanishing orography.    
!!            
!!               * anelastic reference state variables :
!!
!!                   1D reference state : 
!!                     RSOU and CSTN cases : rhorefz and thvrefz are computed 
!!                         by   SET_REFZ (called by SET_MASS).
!!                         They are deduced from thetav and r on the model grid
!!                         without orography.
!!                   The 3D reference state is  computed by SET_REF   
!!            
!!               * The total mass of dry air is computed by TOTAL_DMASS              
!!
!!             - writes the DESFM file, 
!!
!!             - writes the LFIFM file . 
!!
!!    EXTERNAL
!!    --------
!!      DEFAULT_DESFM : to set default values for variables which can be 
!!                      contained in DESFM file
!!      DEFAULT_EXPRE : to  set default values for other global variables 
!!                      which can be contained in namelist-part of EXPRE 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_RSOU      : to initialize mass fields from a radiosounding
!!      SET_CSTN      : to initialize mass fields from a vertical profile of 
!!                      n layers of Nv=cste 
!!      SET_REF       : to compute  rhoJ 
!!      RESSURE_IN_PREP : to apply an anelastic correction in the case of
!!                        non-vanishing orography 
!!      FMOPEN        : to open a FM-file (DESFM + LFIFM)
!!      WRITE_DESFM   : to write the  DESFM file
!!      WRI_LFIFM     : to write the   LFIFM file  
!!      FMCLOS        : to close a FM-file (DESFM + LFIFM)
!!
!!      MXM,MYM,MZM   : Shuman operators
!!      WGUESS        : to compute W with the continuity equation from 
!!                      the U,V values 
!!
!!
!!      
!!    IMPLICIT ARGUMENTS
!!    ------------------
!!      Module MODD_PARAMETERS : contains parameters
!!      Module MODD_DIM1      : contains dimensions 
!!      Module MODD_CONF       : contains  configuration variables for 
!!                                all models
!!      Module MODD_CST        : contains physical constants
!!      Module MODD_GRID       : contains grid variables  for all models
!!      Module MODD_GRID1     : contains grid variables
!!      Module MODD_TIME      : contains time variables for all models  
!!      Module MODD_TIME1     : contains time variables  
!!      Module MODD_REF        : contains reference state variables for
!!                               all models
!!      Module MODD_REF1      : contains reference state variables 
!!      Module MODD_LUNIT      : contains variables which concern names
!!                            and logical unit numbers of files  for all models
!!      Module MODD_FIELD1    : contains prognostics  variables
!!      Module MODD_GR_FIELD1 : contains the surface prognostic variables 
!!      Module MODD_LSFIELD1    : contains Larger Scale fields
!!      Module MODD_DYN1        : contains dynamic control variables for model 1
!!      Module MODD_LBC1        : contains lbc control variables for model 1
!!
!!
!!      Module MODN_CONF1    : contains  configuration variables for model 1
!!                               and the NAMELIST list
!!      Module MODN_LUNIT1    : contains variables which concern names
!!                               and logical unit numbers of files and 
!!                               the NAMELIST list
!!
!!
!!    REFERENCE
!!    ---------
!!      Book2 of MESO-NH documentation (program PREP_IDEAL_CASE)
!!    
!!    AUTHOR
!!    ------
!!	V. Ducrocq   *Meteo France*
!!
!!    MODIFICATIONS
!!    -------------
!!      Original                            05/05/94
!!      updated                V. Ducrocq   27/06/94   
!!      updated                P.M.         27/07/94
!!      updated                V. Ducrocq   23/08/94 
!!      updated                V. Ducrocq   01/09/94 
!!      namelist changes       J. Stein     26/10/94 
!!      namelist changes       J. Stein     04/11/94 
!!      remove the second step of the geostrophic balance 14/11/94 (J.Stein)
!!      add grid stretching in the z direction + Larger scale fields +
!!      cleaning                                           6/12/94 (J.Stein) 
!!      periodize the orography and the grid sizes in the periodic case
!!                                                        19/12/94 (J.Stein) 
!!      correct a bug in the Larger Scale Fields initialization
!!                                                        19/12/94 (J.Stein) 
!!      add the vertical grid stretching                  02/01/95 (J. Stein)
!!      Total mass of dry air computation                 02/01/95 (J.P.Lafore) 
!!      add the 1D switch                                 13/01/95 (J. Stein)
!!      enforce a regular vertical grid if desired        18/01/95 (J. Stein)
!!      add the tdtcur initialization                     26/01/95 (J. Stein)
!!      bug in the test of the type of RS localization    25/02/95 (J. Stein)
!!      remove R from the historical variables            16/03/95 (J. Stein)
!!      error on the grid stretching                      30/06/95 (J. Stein)
!!      add the soil fields                               01/09/95 (S.Belair)
!!      change the streching function  and the wind guess
!!        (J. Stein and V.Masson)                         21/09/95 
!!      reset to FALSE LUSERC,..,LUSERH                   12/12/95 (J. Stein)
!!      enforce the RS localization in 1D and 2D config.
!!      + add the 'TSZ0' option for the soil variables    28/01/96 (J. Stein)
!!      initialization of domain from center point        31/01/96 (V. Masson)
!!      add the constant file reading                     05/02/96 (J. Stein)
!!      enter vertical model levels values                20/10/95 (T.Montmerle)
!!      add LFORCING option                               19/02/96 (K. Suhre)
!!      modify structure of NAM_CONF_PRE                  20/02/96 (J.-P. Pinty)
!!      default of the domain center when use of pgd file 12/03/96 (V. Masson)
!!      change the surface initialization                 20/03/96 ( Stein,
!!                                                    Bougeault, Kastendeutsch )
!!      change the DEFAULT_DESFMN CALL                    17/04/96 ( Lafore )
!!      set the STORAGE_TYPE to 'TT' (a single instant)   30/04/96 (Stein, 
!!                                                    Jabouille)
!!      new wguess to spread  the divergence              15/05/96 (Stein)
!!      set LTHINSHELL to TRUE + return to the old wguess 29/08/96 (Stein)
!!      MY_NAME and DAD_NAME writing for nesting          30/07/96 (Lafore)
!!      MY_NAME and DAD_NAME reading in pgd file          26/09/96 (Masson)
!!       and reading of pgd grid in a new routine
!!      XXHAT and XYHAT are set to 0. at origine point    02/10/96 (Masson)
!!      add LTHINSHELL in namelist NAM_CONF_PRE           08/10/96 (Masson)
!!      restores use of TS and T2                         26/11/96 (Masson)
!!      value  XUNDEF for soil and vegetation fields on sea 27/11/96 (Masson)
!!      use of HUG and HU2 in both ISBA and TSZ0 cases    04/12/96 (Masson)
!!      add initialization of chemical variables          06/08/96 (K. Suhre)
!!      add MANUAL option for the terrain elevation       12/12/96 (J.-P. Pinty)
!!      set DATA instead of MANUAL for the terrain
!!      elevation option
!!      add new anelastic equations' systems              29/06/97 (Stein)
!!      split mode_lfifm_pgd                              29/07/97 (Masson)
!!      add directional z0 and subgrid scale orography    31/07/97 (Masson)
!!      separates surface treatment in PREP_IDEAL_SURF    15/03/99 (Masson)
!!      new PGD fields allocations                        15/03/99 (Masson)
!!      iterative call to pressure solver                 15/03/99 (Masson)
!!      removes TSZ0 case                                 04/01/00 (Masson)
!!      parallelization                                   18/06/00 (Pinty)
!!      adaptation for patch approach                     02/07/00 (Solmon/Masson)
!!      bug in W LB field on Y direction                  05/03/01 (Stein)
!!      add module MODD_NSV for NSV variable              01/02/01 (D. Gazen) 
!!      allow namelists in different orders               15/10/01 (I. Mallet)
!!      allow LUSERC and LUSERI in 1D configuration       05/06/02 (P. Jabouille)
!!      add  ZUVTHLMR case (move in set_rsou latter)      05/12/02 Jabouille/Masson
!!      move LHORELAX_SV (after INI_NSV)                  30/04/04 (Pinty)
!!      Correction Parallel bug IBEG & IDEND  evalution   13/11/08 J.Escobar
!!      add the option LSHIFT for interpolation of        26/10/10 (G.Tanguy)
!!      correction for XHAT & parallelizarion of ZSDATA   23/09/11 J.Escobar
!!      the vertical profile (as in PREP_REAL_CASE)
!!      add use MODI of SURFEX routines                   10/10/111 J.Escobar
!!
!!      For 2D modeling: 
!!      Initialization of ADVFRC profiles (SET_ADVFRC)    06/2010 (P.Peyrille)
!!      when LDUMMY(2)=T in PRE_IDEA1.nam 
!!      USE MODDB_ADVFRC_n for grid-nesting               02*2012 (M. Tomasini)
!!      LBOUSS in MODD_REF                                07/2013 (C.Lac)
!-------------------------------------------------------------------------------
!
!*       0.   DECLARATIONS
!             ------------
!
USE MODD_PARAMETERS       ! Declarative modules
USE MODD_DIM_n
USE MODD_CONF
USE MODD_CST
USE MODD_GRID         
USE MODD_GRID_n
USE MODD_METRICS_n
USE MODD_PGDDIM
USE MODD_PGDGRID
USE MODD_TIME
USE MODD_TIME_n
USE MODD_REF
USE MODD_REF_n
USE MODD_LUNIT
USE MODD_FIELD_n
USE MODD_DYN_n
USE MODD_LBC_n
USE MODD_LSFIELD_n
USE MODD_PARAM_n
USE MODD_CH_MNHC_n, ONLY:  LUSECHEM, LUSECHAQ, LUSECHIC, LCH_PH,  &
                           LCH_INIT_FIELD, CCHEM_INPUT_FILE 
USE MODD_CH_AEROSOL,ONLY:  LORILAM, CORGANIC, LVARSIGI, LVARSIGJ, LINITPM, XINIRADIUSI, &
                           XINIRADIUSJ, XINISIGI, XINISIGJ, XN0IMIN, XN0JMIN, CRGUNIT
USE MODD_DUST,      ONLY:  LDUST, NMODE_DST, CRGUNITD, XINISIG, XINIRADIUS, XN0MIN 
USE MODD_SALT,      ONLY:  LSALT, NMODE_SLT, CRGUNITS, XINISIG_SLT, XINIRADIUS_SLT, XN0MIN_SLT
USE MODD_VAR_ll,    ONLY:  NPROC
USE MODD_LUNIT_n
USE MODD_CONF_n
USE MODD_NSV,      ONLY : NSV,NSV_CHEM,           &
                          NSV_DSTEND, NSV_DSTBEG
!
USE MODN_BLANK
!
USE MODE_THERMO
USE MODE_POS
USE MODE_GRIDCART         ! Executive modules
USE MODE_GRIDPROJ
USE MODE_FM
USE MODE_FMREAD
USE MODE_IO_ll
USE MODE_ll
USE MODD_ARGSLIST_ll, ONLY : LIST_ll
USE MODE_MODELN_HANDLER
!
USE MODI_DEFAULT_DESFM_n    ! Interface modules
USE MODI_DEFAULT_EXPRE
USE MODI_READ_HGRID
USE MODI_SHUMAN
USE MODI_SET_RSOU
USE MODI_SET_CSTN
USE MODI_SET_FRC
USE MODI_PRESSURE_IN_PREP
USE MODI_WRITE_DESFM_n
USE MODI_WRITE_LFIFM_n
USE MODI_METRICS
USE MODI_UPDATE_METRICS
USE MODI_SET_REF
USE MODI_SET_PERTURB
USE MODI_TOTAL_DMASS
USE MODI_WGUESS
USE MODI_CH_INIT_SCHEME_n
USE MODI_CH_INIT_FIELD_n
USE MODI_GATHER_ll
USE MODI_INI_NSV
USE MODI_READ_PRE_IDEA_NAM_n
USE MODI_CH_AER_INIT_SOA
USE MODI_ZSMT_PIC
USE MODI_READ_VER_GRID
USE MODI_READ_ALL_NAMELISTS
USE MODI_GOTO_SURFEX
USE MODI_PGD_GRID_SURF_ATM
USE MODI_SPLIT_GRID
USE MODI_PGD_SURF_ATM
USE MODI_ICE_ADJUST_BIS
388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883
USE MODI_WRITE_PGD_SURF_ATM_n
USE MODI_PREP_SURF_MNH
USE MODI_ALLOC_SURFEX
!
!JUAN
USE MODE_SPLITTINGZ_ll
USE MODD_SUB_MODEL_n
USE MODE_MNH_TIMING
USE MODN_CONFZ
!JUAN
#ifdef MNH_NCWRIT
USE MODN_NCOUT
USE MODE_UTIL
#endif
USE MODI_TH_R_FROM_THL_RT_3D
!
USE MODI_VERSION
USE MODI_INIT_PGD_SURF_ATM
USE MODI_WRITE_SURF_ATM_N
USE MODI_DEALLOC_SURF_ATM_N
USE MODI_DEALLOC_SURFEX
! Modif ADVFRC
USE MODD_2D_FRC
USE MODD_ADVFRC_n     ! Modif for grid-nesting
USE MODI_SETADVFRC
USE MODD_RELFRC_n     ! Modif for grid-nesting
USE MODI_SET_RELFRC
!
USE MODI_INI_CST
USE MODI_INI_NEB
!
IMPLICIT NONE
!
!*       0.1  Declarations of global variables not declared in the modules
!
REAL, DIMENSION(:,:,:), ALLOCATABLE :: XJ ! Jacobian
REAL :: XLATCEN=XUNDEF, XLONCEN=XUNDEF ! latitude and longitude of the center of
                                     ! the domain for initialization. This 
                                     ! point is vertical vorticity point
                                     !          ------------------------
REAL :: XDELTAX=0.5E4, XDELTAY=0.5E4 ! horizontal mesh lengths  
                                     !  used to determine  XXHAT,XYHAT
!
INTEGER :: NLUPRE,NLUOUT           ! Logical unit numbers for EXPRE file
                                   ! and for output_listing file
INTEGER :: NRESP                   ! return code in FM routines
INTEGER :: NTYPE                   ! type of file (cpio or not)
INTEGER :: NNPRAR                  ! number of articles predicted  in
                                   !  the LFIFM file
INTEGER :: NNINAR                  ! number of articles  present in
                                   !  the LFIFM file
LOGICAL :: GFOUND                  ! Return code when searching namelist
!
INTEGER :: JLOOP,JILOOP,JJLOOP     ! Loop indexes
!
INTEGER :: NIB,NJB,NKB             ! Begining useful area  in x,y,z directions
INTEGER :: NIE,NJE                 ! Ending useful area  in x,y directions
INTEGER :: NIU,NJU,NKU             ! Upper bounds in x,y,z directions
CHARACTER (LEN=32) ::  CEXPRE            ! name of the EXPRE file
CHARACTER (LEN=32) :: CDESFM             ! Name of DESFM file 
CHARACTER(LEN=4)   :: CIDEAL ='CSTN'     ! kind of idealized fields
                                         ! 'CSTN' : Nv=cste case 
                                         ! 'RSOU' : radiosounding case
CHARACTER(LEN=4)   :: CZS    ='FLAT'     ! orography selector
                                         ! 'FLAT' : zero orography
                                         ! 'SINE' : sine-shaped orography 
                                         ! 'BELL' : bell-shaped orography 
REAL    :: XHMAX=XUNDEF            ! Maximum height for orography
REAL    :: NEXPX=3,NEXPY=1         ! Exponents for  orography in case of CZS='SINE'
REAL    :: XAX= 1.E4, XAY=1.E4     ! Widths for orography in case CZS='BELL'
                                   ! along x and y 
INTEGER :: NIZS = 5, NJZS = 5      ! Localization of the center in 
                                   ! case CZS ='BELL' 
!
!*       0.1.1 Declarations of local variables for N=cste and 
!              radiosounding cases :
!
INTEGER            :: NYEAR,NMONTH,NDAY ! year, month and day in EXPRE file
REAL               :: XTIME             ! time in EXPRE file
LOGICAL            :: LPERTURB =.FALSE. ! Logical to add a perturbation to 
                                        ! a basic state 
LOGICAL            :: LGEOSBAL =.FALSE. ! Logical to satisfy the geostrophic
                                        ! balance
                                        ! .TRUE. for geostrophic balance
                                        ! .FALSE. to ignore this balance
LOGICAL            :: LPV_PERT =.FALSE. ! Logical to add a PV pertubation
LOGICAL            :: LRMV_BL  =.FALSE. ! Logical to remove the boundary layer
                                        ! before PV inversion
LOGICAL            :: LSHIFT   =.FALSE.  ! flag to perform vertical shift or not.        
CHARACTER(LEN=3)   :: CFUNU ='ZZZ'      ! CHARACTER STRING for variation of
                                        ! U in y direction
                                        ! 'ZZZ'  : U = U(Z)
                                        ! 'Y*Z'  : U = F(Y) * U(Z)
                                        ! 'Y,Z'  : U = G(Y,Z)
CHARACTER(LEN=3)   :: CFUNV ='ZZZ'      ! CHARACTER STRING for variation of
                                        ! V in x direction
                                        ! 'ZZZ'  : V = V(Z)
                                        ! 'Y*Z'  : V = F(X) * V(Z)
                                        ! 'Y,Z'  : V = G(X,Z)
CHARACTER(LEN=6)   :: CTYPELOC='IJGRID' ! Type of informations  used to give the
                                        ! localization of vertical profile
                                        ! 'IJGRID'  for (i,j) point  on index space
                                        ! 'XYHATM' for (x,y) coordinates on
                                        !  conformal or cartesian plane
                                        ! 'LATLON' for (latitude,longitude) on
                                        !   spherical earth  
REAL               :: XLATLOC= 45., XLONLOC=0.
                                        ! Latitude and longitude of the vertical
                                        ! profile localization  (used in case 
                                        ! CTYPELOC='LATLON') 
REAL               :: XXHATLOC=2.E4, XYHATLOC=2.E4 
                                        ! (x,y) of the vertical profile
                                        ! localization  (used in cases 
                                        ! CTYPELOC='LATLON' and 'XYHATM') 
INTEGER, DIMENSION(1) :: NILOC=4, NJLOC=4 
                                        ! (i,j) of the vertical profile
                                        ! localization 
!
!
REAL,DIMENSION(:,:,:),ALLOCATABLE   :: XCORIOZ ! Coriolis parameter (this
                                                 ! is exceptionnaly a 3D array
                                                 ! for computing needs)
!
!
!*       0.1.2 Declarations of local variables used when a PhysioGraphic Data
!              file is used :
!
INTEGER             :: JSV                      ! loop index on scalar var.
CHARACTER(LEN=28)   :: CPGD_FILE=' '            ! Physio-Graphic Data file name
LOGICAL  :: LREAD_ZS = .TRUE.,                & ! switch to use orography 
                                                ! coming from the PGD file
            LREAD_GROUND_PARAM = .TRUE.         ! switch to use soil parameters
                                                ! useful for the soil scheme
                                                ! coming from the PGD file

INTEGER           :: NSLEVE   =12         ! number of iteration for smooth orography
REAL              :: XSMOOTH_ZS = XUNDEF  ! optional uniform smooth orography for SLEVE coordinate
CHARACTER(LEN=28) :: YPGD_NAME, YPGD_DAD_NAME   ! general information
CHARACTER(LEN=8)  :: YKIND                      ! Kind of radiosounding data
CHARACTER(LEN=2)  :: YPGD_TYPE
!
INTEGER           :: IINFO_ll                   ! return code of // routines
TYPE(LIST_ll), POINTER :: TZ_FIELDS_ll           ! list of metric coefficient fields
!
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       ! North-south LB arrays
INTEGER :: IBEG,IEND,IXOR,IXDIM,IYOR,IYDIM,ILBX,ILBY
REAL, DIMENSION(:),   ALLOCATABLE :: ZXHAT_ll, ZYHAT_ll
!
REAL, DIMENSION(:,:,:), ALLOCATABLE ::ZTHL,ZT,ZRT,ZFRAC_ICE,&
                                      ZEXN,ZLVOCPEXN,ZLSOCPEXN,ZCPH, &
                                      ZRSATW, ZRSATI
                                 ! variables for adjustement
INTEGER             :: ILENCH, IGRID, IRESP
CHARACTER (LEN=100) :: YCOMMENT
REAL                :: ZDIST
!
!JUAN TIMING
REAL*8,DIMENSION(2)         :: ZTIME1,ZTIME2,ZEND,ZTOT
CHARACTER                 :: YMI
INTEGER                   :: IMI
INTEGER::JK                                 
!JUAN TIMING
!
REAL, DIMENSION(:),   ALLOCATABLE :: ZZS_ll
INTEGER                           :: IJ 
!
!
!*       0.2  Namelist declarations
!
NAMELIST/NAM_CONF_PRE/ LTHINSHELL,LCARTESIAN,    &! Declarations in MODD_CONF
                       LPACK,                    &!
                       NVERB,CIDEAL,CZS,         &!+global variables initialized
                       LBOUSS,LPERTURB,LPV_PERT, &! at their declarations
                       LRMV_BL,LFORCING,CEQNSYS, &! at their declarations
                       LSHIFT,L2D_ADV_FRC,L2D_REL_FRC
NAMELIST/NAM_GRID_PRE/ XLON0,XLAT0,            & ! Declarations in MODD_GRID
                       XBETA,XRPK,             & 
                       XLONORI,XLATORI
NAMELIST/NAM_GRIDH_PRE/ XLATCEN,XLONCEN,       & ! local variables  initialized
                 XDELTAX,XDELTAY,              & ! at their declarations
                 XHMAX,NEXPX,NEXPY,            &
                 XAX,XAY,NIZS,NJZS
NAMELIST/NAM_VPROF_PRE/LGEOSBAL, CFUNU,CFUNV,   &! global variables initialized
                     CTYPELOC,XLATLOC,XLONLOC,  &!  at their declarations
                     XXHATLOC,XYHATLOC,NILOC,NJLOC
NAMELIST/NAM_REAL_PGD/CPGD_FILE,                 & ! Physio-Graphic Data file
                                                   !  name
                      LREAD_ZS,                  & ! switch to use orography 
                                                   ! coming from the PGD file
                      LREAD_GROUND_PARAM
NAMELIST/NAM_SLEVE/NSLEVE, XSMOOTH_ZS
!
!*       0.3  Auxillary Namelist declarations
!
NAMELIST/NAM_AERO_PRE/ LORILAM, LINITPM, XINIRADIUSI, XINIRADIUSJ, &
                       XINISIGI, XINISIGJ, XN0IMIN, XN0JMIN, CRGUNIT, &
                       LDUST, LSALT, CRGUNITD, CRGUNITS,&
                       NMODE_DST, XINISIG, XINIRADIUS, XN0MIN,&
                       XINISIG_SLT, XINIRADIUS_SLT, XN0MIN_SLT, &
                       NMODE_SLT
!
!-------------------------------------------------------------------------------
!
!*       0.    PROLOGUE
!              --------
!
CALL GOTO_MODEL(1)
!
CALL INITIO_ll()
NULLIFY(TZ_FIELDS_ll)
CALL VERSION
CPROGRAM='IDEAL '
!
!JUAN TIMING
  XT_START     = 0.0
  XT_STORE     = 0.0
!
  CALL SECOND_MNH2(ZEND)
!
!JUAN TIMING
!
!*       1.    INITIALIZE PHYSICAL CONSTANTS :         
!              ------------------------------
!
NVERB = 5
CALL INI_CST
CALL INI_NEB
!
!-------------------------------------------------------------------------------
!
!
!*  	 2.    SET DEFAULT VALUES  :  
!              --------------------
!
!
!*       2.1  For variables in DESFM file
!
CALL DEFAULT_DESFM_n(1)
!
CSURF = "NONE"
!
!
!*       2.2  For other global variables in EXPRE file
!
CALL DEFAULT_EXPRE
!-------------------------------------------------------------------------------
!
!*  	 3.    READ THE EXPRE FILE :  
!              --------------------
!
!*       3.1   initialize logical unit numbers (EXPRE and output-listing files)
!              and open these files :
! 
! 
CLUOUT  = 'OUTPUT_LISTING1'
CLUOUT0 = CLUOUT
CEXPRE  = 'PRE_IDEA1.nam'
CALL OPEN_ll(UNIT=NLUOUT,FILE=CLUOUT,IOSTAT=NRESP,FORM='FORMATTED',ACTION='WRITE', &
     MODE=GLOBAL)
CALL OPEN_ll(UNIT=NLUPRE,FILE=CEXPRE,IOSTAT=NRESP,ACTION='READ', &
     DELIM='QUOTE',MODE=GLOBAL)    
!
!*       3.2   read in NLUPRE the namelist informations
!
WRITE(NLUOUT,FMT=*) 'attempt to read ',TRIM(CEXPRE),' file'
CALL POSNAM(NLUPRE,'NAM_REAL_PGD',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_REAL_PGD)
!
!
CALL POSNAM(NLUPRE,'NAM_CONF_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_CONF_PRE)
!JUANZ
CALL POSNAM(NLUPRE,'NAM_CONFZ',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_CONFZ)
!JUANZ
#ifdef MNH_NCWRIT
CALL POSNAM(NLUPRE,'NAM_NCOUT',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_NCOUT)
#endif
CALL POSNAM(NLUPRE,'NAM_GRID_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_GRID_PRE)
CALL POSNAM(NLUPRE,'NAM_GRIDH_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_GRIDH_PRE)
CALL POSNAM(NLUPRE,'NAM_VPROF_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_VPROF_PRE)
CALL POSNAM(NLUPRE,'NAM_BLANK',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_BLANK)
CALL READ_PRE_IDEA_NAM_n(NLUPRE,NLUOUT)
CALL POSNAM(NLUPRE,'NAM_AERO_PRE',GFOUND,NLUOUT)
IF (GFOUND) READ(UNIT=NLUPRE,NML=NAM_AERO_PRE)
!
IF( LEN_TRIM(CPGD_FILE) /= 0 ) THEN 
  ! open the PGD_FILE
  CALL FMOPEN_ll(CPGD_FILE,'READ',CLUOUT,NNPRAR,2,NVERB,NNINAR,NRESP)
  ! read the grid in the PGD file
  CALL FMREAD(CPGD_FILE,'IMAX',CLUOUT,'--',NIMAX,IGRID,ILENCH,YCOMMENT,IRESP)
  CALL FMREAD(CPGD_FILE,'JMAX',CLUOUT,'--',NJMAX,IGRID,ILENCH,YCOMMENT,IRESP)
END IF
!
NIMAX_ll=NIMAX   !! _ll variables are global variables
NJMAX_ll=NJMAX   !! but the old names are kept in PRE_IDEA1.nam file
!
!*       3.3   check some parameters:
!
L1D=.FALSE. ; L2D=.FALSE.
!
IF ((NIMAX == 1).OR.(NJMAX == 1)) THEN 
  L2D=.TRUE.
  NJMAX_ll=1
  NIMAX_ll=MAX(NIMAX,NJMAX)
  WRITE(NLUOUT,FMT=*) ' NJMAX HAS BEEN SET TO 1 SINCE 2D INITIAL FILE IS REQUIRED &
                   & (L2D=TRUE) )' 
END IF
!
IF ((NIMAX == 1).AND.(NJMAX == 1)) THEN 
  L1D=.TRUE.
  NIMAX_ll = 1
  NJMAX_ll = 1
  WRITE(NLUOUT,FMT=*) ' 1D INITIAL FILE IS REQUIRED (L1D=TRUE) ' 
END IF
!
IF(.NOT. L1D) THEN
  LHORELAX_UVWTH=.TRUE.
  LHORELAX_RV=.TRUE.
ENDIF
!
NRIMX= MIN(JPRIMMAX,NIMAX_ll/2)
!
IF (L2D) THEN
  NRIMY=0
ELSE
  NRIMY= MIN(JPRIMMAX,NJMAX_ll/2)
END IF
!
IF (L1D) THEN
  NRIMX=0
  NRIMY=0
END IF
!
IF (L1D .AND. ( LPERTURB .OR. LGEOSBAL .OR.                &
               (.NOT. LCARTESIAN ) .OR. (.NOT. LTHINSHELL) ))THEN 
  LGEOSBAL   = .FALSE.
  LPERTURB   = .FALSE.
  LCARTESIAN = .TRUE. 
  LTHINSHELL = .TRUE. 
  WRITE(NLUOUT,FMT=*) ' LGEOSBAL AND LPERTURB HAVE BEEN SET TO FALSE &
                      & AND LCARTESIAN AND LTHINSHELL TO TRUE        &
                      & SINCE 1D INITIAL FILE IS REQUIRED (L1D=TRUE)' 
END IF
!
IF (LGEOSBAL .AND. LSHIFT ) THEN
  LSHIFT=.FALSE.
  WRITE(NLUOUT,FMT=*) ' LSHIFT HAS BEEN SET TO FALSE SINCE &
                        & LGEOSBAL=.TRUE. IS REQUIRED '
END IF
!                      
!*       3.4   compute the number of moist variables :
!
IF (.NOT.LUSERV) THEN
  LUSERV = .TRUE.
  WRITE(NLUOUT,FMT=*) ' LUSERV HAS BEEN RESET TO TRUE, SINCE A MOIST VARIABLE &
                   & IS PRESENT IN EXPRE FILE (CIDEAL = RSOU OR CSTN)' 
END IF
!
IF((LUSERI .OR. LUSERC).AND. (CIDEAL /= 'RSOU')) THEN
  WRITE(NLUOUT,FMT=*) 'USE OF HYDROMETEORS IS ONLY ALLOWED IN RSOU CASE'
  WRITE(NLUOUT,FMT=*) '-> JOB ABORTED'
   !callabortstop
   CALL CLOSE_ll(CLUOUT,IOSTAT=IRESP)
   CALL ABORT
  STOP
ENDIF
IF (LUSERI) THEN
  LUSERC =.TRUE.
  LUSERR =.TRUE.
  LUSERI =.TRUE.
  LUSERS =.TRUE.
  LUSERG =.TRUE.
  LUSERH =.FALSE.
  CCLOUD='ICE3'
ELSEIF(LUSERC) THEN
  LUSERR =.FALSE.
  LUSERI =.FALSE.
  LUSERS =.FALSE.
  LUSERG =.FALSE.
  LUSERH =.FALSE.
  CCLOUD='REVE'
ELSE
  LUSERC =.FALSE.
  LUSERR =.FALSE.
  LUSERI =.FALSE.
  LUSERS =.FALSE.
  LUSERG =.FALSE.
  LUSERH =.FALSE.
  LHORELAX_RC=.FALSE.
  LHORELAX_RR=.FALSE.
  LHORELAX_RI=.FALSE.
  LHORELAX_RS=.FALSE.
  LHORELAX_RG=.FALSE.
  LHORELAX_RH=.FALSE.
  CCLOUD='NONE'
!
END IF
!
NRR=0
IF (LUSERV) NRR=NRR+1
IF (LUSERC) NRR=NRR+1
IF (LUSERR) NRR=NRR+1
IF (LUSERI) NRR=NRR+1
IF (LUSERS) NRR=NRR+1
IF (LUSERG) NRR=NRR+1
IF (LUSERH) NRR=NRR+1
!
! NRR=4 for RSOU case because RI and Rc always computed
IF (CIDEAL == 'RSOU' .AND. NRR < 4 ) NRR=4
!                   
!
!*       3.5   Chemistry
!
IF (LORILAM .OR. LCH_INIT_FIELD) THEN
  ! Always initialize chemical scheme variables before INI_NSV call !
  CALL CH_INIT_SCHEME_n(1,LUSECHAQ,LUSECHIC,LCH_PH,NLUOUT,NVERB)
  LUSECHEM = .TRUE.
  IF (LORILAM) THEN
    CORGANIC = "MPMPO"
    LVARSIGI = .TRUE.
    LVARSIGJ = .TRUE.
    CALL CH_AER_INIT_SOA(NLUOUT, NVERB)
  END IF
END IF
! initialise NSV_* variables
CALL INI_NSV(1)
LHORELAX_SV(:)=.FALSE.
IF(.NOT. L1D) LHORELAX_SV(1:NSV)=.TRUE.
!
!-------------------------------------------------------------------------------
!
!*       4.    ALLOCATE MEMORY FOR ARRAYS :  
!   	       ----------------------------
!
!*       4.1  Vertical Spatial grid 
!
CALL READ_VER_GRID(CEXPRE)
!
!*       4.2  Initialize parallel variables and compute array's dimensions
!
!
IF(LGEOSBAL) THEN
  CALL SET_SPLITTING_ll('XSPLITTING')  ! required for integration of thermal wind balance
ELSE
  CALL SET_SPLITTING_ll('BSPLITTING')
ENDIF
CALL SET_JP_ll(1,JPHEXT,JPVEXT,JPHEXT)
CALL SET_DAD0_ll()
CALL SET_DIM_ll(NIMAX_ll, NJMAX_ll, NKMAX)
CALL SET_FMPACK_ll(L1D,L2D,LPACK)
CALL SET_LBX_ll(CLBCX(1), 1)
CALL SET_LBY_ll(CLBCY(1), 1)
CALL SET_XRATIO_ll(1, 1)
CALL SET_YRATIO_ll(1, 1)
CALL SET_XOR_ll(1, 1)
CALL SET_XEND_ll(NIMAX_ll+2*JPHEXT, 1)
CALL SET_YOR_ll(1, 1)
CALL SET_YEND_ll(NJMAX_ll+2*JPHEXT, 1)
CALL SET_DAD_ll(0, 1)
CALL INI_PARAZ_ll(IINFO_ll)
!
! sizes of arrays of the extended sub-domain
!
CALL GET_DIM_EXT_ll('B',NIU,NJU)
CALL GET_DIM_PHYS_ll('B',NIMAX,NJMAX)
CALL GET_INDICE_ll(NIB,NJB,NIE,NJE)
CALL GET_OR_ll('B',IXOR,IYOR)
NKB=1+JPVEXT
NKU=NKMAX+2*JPVEXT
!
!*       4.3  Global variables absent from the modules :
!
ALLOCATE(XJ(NIU,NJU,NKU))
SELECT CASE(CIDEAL)
  CASE('RSOU','CSTN')
    IF (LGEOSBAL) ALLOCATE(XCORIOZ(NIU,NJU,NKU))  ! exceptionally a 3D array  
  CASE DEFAULT                      ! undefined preinitialization
    WRITE(NLUOUT,FMT=*) 'PREP_IDEAL_CASE : CIDEAL IS NOT CORRECTLY DEFINED'
    WRITE(NLUOUT,FMT=*) '-> JOB ABORTED'
   !callabortstop
   CALL CLOSE_ll(CLUOUT,IOSTAT=IRESP)
   CALL ABORT
    STOP
END SELECT 
!
!*       4.4   Prognostic variables at M instant (module MODD_FIELD1):
!
ALLOCATE(XUT(NIU,NJU,NKU))
ALLOCATE(XVT(NIU,NJU,NKU))
ALLOCATE(XWT(NIU,NJU,NKU))
ALLOCATE(XTHT(NIU,NJU,NKU))
ALLOCATE(XPABST(NIU,NJU,NKU))
ALLOCATE(XRT(NIU,NJU,NKU,NRR))
ALLOCATE(XSVT(NIU,NJU,NKU,NSV))
!
!*       4.5   Grid variables (module MODD_GRID1 and MODD_METRICS1):
!
ALLOCATE(XMAP(NIU,NJU))
ALLOCATE(XLAT(NIU,NJU))
ALLOCATE(XLON(NIU,NJU))
ALLOCATE(XDXHAT(NIU),XDYHAT(NJU))
IF (LEN_TRIM(CPGD_FILE)==0) ALLOCATE(XZS(NIU,NJU))
IF (LEN_TRIM(CPGD_FILE)==0) ALLOCATE(ZZS_ll(NIMAX_ll))
IF (LEN_TRIM(CPGD_FILE)==0) ALLOCATE(XZSMT(NIU,NJU))
ALLOCATE(XZZ(NIU,NJU,NKU))
!
ALLOCATE(XDXX(NIU,NJU,NKU))
ALLOCATE(XDYY(NIU,NJU,NKU))
ALLOCATE(XDZX(NIU,NJU,NKU))
ALLOCATE(XDZY(NIU,NJU,NKU))
ALLOCATE(XDZZ(NIU,NJU,NKU))
!
!*       4.6   Reference state variables (modules MODD_REF and MODD_REF1):
!
ALLOCATE(XRHODREFZ(NKU),XTHVREFZ(NKU))
XTHVREFZ(:)=0.0
IF(CEQNSYS == 'DUR') THEN
  ALLOCATE(XRVREF(NIU,NJU,NKU))
ELSE
  ALLOCATE(XRVREF(0,0,0))
END IF
ALLOCATE(XRHODREF(NIU,NJU,NKU),XTHVREF(NIU,NJU,NKU),XEXNREF(NIU,NJU,NKU))
ALLOCATE(XRHODJ(NIU,NJU,NKU))
!
!*       4.7   Larger Scale fields (modules MODD_LSFIELD1):
!
ALLOCATE(XLSUM(NIU,NJU,NKU))
ALLOCATE(XLSVM(NIU,NJU,NKU))
ALLOCATE(XLSWM(NIU,NJU,NKU))
ALLOCATE(XLSTHM(NIU,NJU,NKU))
ALLOCATE(XLSRVM(NIU,NJU,NKU))
!
!  allocate lateral boundary field used for coupling
!
IF ( L1D) THEN                         ! 1D case
!
  NSIZELBX_ll=0
  NSIZELBXU_ll=0
  NSIZELBY_ll=0
  NSIZELBYV_ll=0
  NSIZELBXTKE_ll=0
  NSIZELBXR_ll=0
  NSIZELBXSV_ll=0
  NSIZELBYTKE_ll=0
  NSIZELBYR_ll=0
  NSIZELBYSV_ll=0
  ALLOCATE(XLBXUM(0,0,0))
  ALLOCATE(XLBYUM(0,0,0))
  ALLOCATE(XLBXVM(0,0,0))
  ALLOCATE(XLBYVM(0,0,0))
  ALLOCATE(XLBXWM(0,0,0))
  ALLOCATE(XLBYWM(0,0,0))
  ALLOCATE(XLBXTHM(0,0,0))
  ALLOCATE(XLBYTHM(0,0,0))
  ALLOCATE(XLBXTKEM(0,0,0))
  ALLOCATE(XLBYTKEM(0,0,0))
  ALLOCATE(XLBXRM(0,0,0,0))
  ALLOCATE(XLBYRM(0,0,0,0))
  ALLOCATE(XLBXSVM(0,0,0,0))
  ALLOCATE(XLBYSVM(0,0,0,0))
!
ELSEIF( L2D ) THEN             ! 2D case (not yet parallelized)
!                                          
  NSIZELBY_ll=0
  NSIZELBYV_ll=0
  NSIZELBYTKE_ll=0
  NSIZELBYR_ll=0
  NSIZELBYSV_ll=0
  ALLOCATE(XLBYUM(0,0,0))
  ALLOCATE(XLBYVM(0,0,0))
  ALLOCATE(XLBYWM(0,0,0))
  ALLOCATE(XLBYTHM(0,0,0))
  ALLOCATE(XLBYTKEM(0,0,0))
  ALLOCATE(XLBYRM(0,0,0,0))
  ALLOCATE(XLBYSVM(0,0,0,0))
  !
  IF ( LHORELAX_UVWTH ) THEN
    NSIZELBX_ll=2*NRIMX+2
    NSIZELBXU_ll=2*NRIMX+2
    ALLOCATE(XLBXUM(2*NRIMX+2,NJU,NKU))
    ALLOCATE(XLBXVM(2*NRIMX+2,NJU,NKU))
    ALLOCATE(XLBXWM(2*NRIMX+2,NJU,NKU))
    ALLOCATE(XLBXTHM(2*NRIMX+2,NJU,NKU))
  ELSE
    NSIZELBX_ll=2
    NSIZELBXU_ll=4 
    ALLOCATE(XLBXUM(4,NJU,NKU))
    ALLOCATE(XLBXVM(2,NJU,NKU))
    ALLOCATE(XLBXWM(2,NJU,NKU))
    ALLOCATE(XLBXTHM(2,NJU,NKU))
  END IF  
  !
  IF ( NRR > 0 ) THEN
    IF (       LHORELAX_RV .OR. LHORELAX_RC .OR. LHORELAX_RR .OR. LHORELAX_RI    &
          .OR. LHORELAX_RS .OR. LHORELAX_RG .OR. LHORELAX_RH                     &
       ) THEN 
      NSIZELBXR_ll=2* NRIMX+2
      ALLOCATE(XLBXRM(2*NRIMX+2,NJU,NKU,NRR))
    ELSE
      NSIZELBXR_ll=2
      ALLOCATE(XLBXRM(2,NJU,NKU,NRR))
    ENDIF
  ELSE
    NSIZELBXR_ll=0