SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pack_grid_conf_proj.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! ##############################################################
6  SUBROUTINE pack_grid_conf_proj(KMASK_SIZE,KMASK,KGRID_PAR1,PGRID_PAR1,KGRID_PAR2,OPACK,PGRID_PAR2)
7 ! ##############################################################
8 !
9 !!**** *PACK_GRID_CONF_PROJ* packs the grid definition vector
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !! AUTHOR
21 !! ------
22 !!
23 !! V. Masson Meteo-France
24 !!
25 !! MODIFICATION
26 !! ------------
27 !!
28 !! Original 03/2004
29 !!
30 !----------------------------------------------------------------------------
31 !
32 !* 0. DECLARATION
33 ! -----------
34 !
37 !
38 !
39 USE yomhook ,ONLY : lhook, dr_hook
40 USE parkind1 ,ONLY : jprb
41 !
42 IMPLICIT NONE
43 !
44 !* 0.1 Declaration of arguments
45 ! ------------------------
46 !
47 INTEGER, INTENT(IN) :: kmask_size ! size of mask
48 INTEGER, DIMENSION(KMASK_SIZE), INTENT(IN) :: kmask ! mask used
49 INTEGER, INTENT(IN) :: kgrid_par1 ! size of input grid vector
50 REAL, DIMENSION(KGRID_PAR1), INTENT(IN) :: pgrid_par1 ! parameters of input grid
51 INTEGER, INTENT(INOUT) :: kgrid_par2 ! size of output grid vector
52 LOGICAL, INTENT(IN) :: opack ! flag to pack the grid vector
53 REAL, DIMENSION(KGRID_PAR2), INTENT(OUT) :: pgrid_par2 ! parameters of output grid
54 !
55 !* 0.2 Declaration of other local variables
56 ! ------------------------------------
57 !
58 REAL :: zlat0 ! reference latitude
59 REAL :: zlon0 ! reference longitude
60 REAL :: zrpk ! projection parameter
61 ! ! K=1 : stereographic north pole
62 ! ! 0<K<1 : Lambert, north hemisphere
63 ! ! K=0 : Mercator
64 ! !-1<K<0 : Lambert, south hemisphere
65 ! ! K=-1: stereographic south pole
66 REAL :: zbeta ! angle between grid and reference longitude
67 REAL :: zlator ! latitude of point of coordinates X=0, Y=0
68 REAL :: zlonor ! longitude of point of coordinates X=0, Y=0
69 INTEGER :: iimax ! number of points in I direction
70 INTEGER :: ijmax ! number of points in J direction
71 REAL, DIMENSION(:), ALLOCATABLE :: zx1 ! X conformal coordinate of grid mesh
72 REAL, DIMENSION(:), ALLOCATABLE :: zy1 ! Y conformal coordinate of grid mesh
73 REAL, DIMENSION(:), ALLOCATABLE :: zdx1 ! X grid mesh size
74 REAL, DIMENSION(:), ALLOCATABLE :: zdy1 ! Y grid mesh size
75 REAL, DIMENSION(:), ALLOCATABLE :: zx2 ! X conformal coordinate of grid mesh
76 REAL, DIMENSION(:), ALLOCATABLE :: zy2 ! Y conformal coordinate of grid mesh
77 REAL, DIMENSION(:), ALLOCATABLE :: zdx2 ! X grid mesh size
78 REAL, DIMENSION(:), ALLOCATABLE :: zdy2 ! Y grid mesh size
79 
80 INTEGER :: il1 ! number of points of input grid
81 REAL, DIMENSION(:), POINTER :: zgrid_par2 ! parameters of output grid
82 REAL(KIND=JPRB) :: zhook_handle
83 !----------------------------------------------------------------------------
84 !
85 !* 2. Computes grid parameters
86 ! ------------------------
87 !
88 IF (lhook) CALL dr_hook('PACK_GRID_CONF_PROJ',0,zhook_handle)
89  CALL get_gridtype_conf_proj(pgrid_par1,kl=il1)
90 !
91 ALLOCATE(zx1(il1))
92 ALLOCATE(zy1(il1))
93 ALLOCATE(zdx1(il1))
94 ALLOCATE(zdy1(il1))
95 !
96  CALL get_gridtype_conf_proj(pgrid_par1,zlat0,zlon0,zrpk,zbeta,&
97  zlator,zlonor,iimax,ijmax, &
98  zx1,zy1,zdx1,zdy1 )
99 !
100 ALLOCATE(zx2(kmask_size))
101 ALLOCATE(zy2(kmask_size))
102 ALLOCATE(zdx2(kmask_size))
103 ALLOCATE(zdy2(kmask_size))
104 !
105  CALL pack_same_rank(kmask,zx1 ,zx2 )
106  CALL pack_same_rank(kmask,zy1 ,zy2 )
107  CALL pack_same_rank(kmask,zdx1,zdx2)
108  CALL pack_same_rank(kmask,zdy1,zdy2)
109 !
110 DEALLOCATE(zx1 )
111 DEALLOCATE(zy1 )
112 DEALLOCATE(zdx1)
113 DEALLOCATE(zdy1)
114 !
115  CALL put_gridtype_conf_proj(zgrid_par2,zlat0,zlon0,zrpk,zbeta,&
116  zlator,zlonor,iimax,ijmax, &
117  zx2,zy2,zdx2,zdy2 )
118 !
119 IF (opack) THEN
120  pgrid_par2(:) = zgrid_par2(:)
121 ELSE
122  kgrid_par2 = SIZE(zgrid_par2(:))
123 END IF
124 !
125 DEALLOCATE(zgrid_par2)
126 DEALLOCATE(zx2 )
127 DEALLOCATE(zy2 )
128 DEALLOCATE(zdx2)
129 DEALLOCATE(zdy2)
130 IF (lhook) CALL dr_hook('PACK_GRID_CONF_PROJ',1,zhook_handle)
131 !-------------------------------------------------------------------------------
132 !
133 END SUBROUTINE pack_grid_conf_proj
subroutine pack_grid_conf_proj(KMASK_SIZE, KMASK, KGRID_PAR1, PGRID_PAR1, KGRID_PAR2, OPACK, PGRID_PAR2)
subroutine put_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, KIMAX, KJMAX, PX, PY, PDX, PDY)
subroutine get_gridtype_conf_proj(PGRID_PAR, PLAT0, PLON0, PRPK, PBETA, PLATOR, PLONOR, KIMAX, KJMAX, PX, PY, PDX, PDY, KL)