SURFEX v8.1
General documentation of Surfex
pack_grid_ign.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_ign(KMASK_SIZE,KMASK,KGRID_PAR1,PGRID_PAR1,KGRID_PAR2,OPACK,PGRID_PAR2)
7 ! ##############################################################
8 !
9 !!**** *PACK_GRID_IGN* packs the grid definition vector
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !! AUTHOR
21 !! ------
22 !!
23 !! E. Martin Meteo-France
24 !!
25 !! MODIFICATION
26 !! ------------
27 !!
28 !! Original 10/2007
29 !! 07/2011 add maximum domain dimension for output (B. Decharme)
30 !----------------------------------------------------------------------------
31 !
32 !* 0. DECLARATION
33 ! -----------
34 !
35 USE modd_surfex_mpi, ONLY : nrank
36 !
39 !
40 USE yomhook ,ONLY : lhook, dr_hook
41 USE parkind1 ,ONLY : jprb
42 !
43 IMPLICIT NONE
44 !
45 !* 0.1 Declaration of arguments
46 ! ------------------------
47 !
48 INTEGER, INTENT(IN) :: KMASK_SIZE ! size of mask
49 INTEGER, DIMENSION(KMASK_SIZE), INTENT(IN) :: KMASK ! mask used
50 INTEGER, INTENT(IN) :: KGRID_PAR1 ! size of input grid vector
51 REAL, DIMENSION(KGRID_PAR1), INTENT(IN) :: PGRID_PAR1 ! parameters of input grid
52 INTEGER, INTENT(INOUT) :: KGRID_PAR2 ! size of output grid vector
53 LOGICAL, INTENT(IN) :: OPACK ! flag to pack the grid vector
54 REAL, DIMENSION(KGRID_PAR2), INTENT(OUT) :: PGRID_PAR2 ! parameters of output grid
55 !
56 !* 0.2 Declaration of other local variables
57 ! ------------------------------------
58 !
59 INTEGER :: ILAMBERT ! Lambert type
60 REAL, DIMENSION(:), ALLOCATABLE :: ZX1 ! X conformal coordinate of grid mesh
61 REAL, DIMENSION(:), ALLOCATABLE :: ZY1 ! Y conformal coordinate of grid mesh
62 REAL, DIMENSION(:), ALLOCATABLE :: ZDX1 ! X grid mesh size
63 REAL, DIMENSION(:), ALLOCATABLE :: ZDY1 ! Y grid mesh size
64 REAL, DIMENSION(:), ALLOCATABLE :: ZX2 ! X conformal coordinate of grid mesh
65 REAL, DIMENSION(:), ALLOCATABLE :: ZY2 ! Y conformal coordinate of grid mesh
66 REAL, DIMENSION(:), ALLOCATABLE :: ZDX2 ! X grid mesh size
67 REAL, DIMENSION(:), ALLOCATABLE :: ZDY2 ! Y grid mesh size
68 !
69 REAL, DIMENSION(:), ALLOCATABLE :: ZXALL ! maximum domain X coordinate of grid mesh
70 REAL, DIMENSION(:), ALLOCATABLE :: ZYALL ! maximum domain Y coordinate of grid mesh
71 INTEGER :: IDIMX ! maximum domain length in X
72 INTEGER :: IDIMY ! maximum domain length in Y
73 !
74 INTEGER :: IL1 ! number of points of input grid
75 REAL, DIMENSION(:), POINTER :: ZGRID_PAR2 ! parameters of output grid
76 REAL(KIND=JPRB) :: ZHOOK_HANDLE
77 !----------------------------------------------------------------------------
78 !
79 !* 2. Computes grid parameters
80 ! ------------------------
81 !
82 IF (lhook) CALL dr_hook('PACK_GRID_IGN',0,zhook_handle)
83  CALL get_gridtype_ign(pgrid_par1,klambert=ilambert,kl=il1)
84 !
85 ALLOCATE(zx1(il1))
86 ALLOCATE(zy1(il1))
87 ALLOCATE(zdx1(il1))
88 ALLOCATE(zdy1(il1))
89 !
90  CALL get_gridtype_ign(pgrid_par1,px=zx1,py=zy1,pdx=zdx1,pdy=zdy1)
91 !
92 ALLOCATE(zx2(kmask_size))
93 ALLOCATE(zy2(kmask_size))
94 ALLOCATE(zdx2(kmask_size))
95 ALLOCATE(zdy2(kmask_size))
96 ALLOCATE(zxall(0))
97 ALLOCATE(zyall(0))
98 !
99  CALL pack_same_rank(kmask,zx1 ,zx2 )
100  CALL pack_same_rank(kmask,zy1 ,zy2 )
101  CALL pack_same_rank(kmask,zdx1,zdx2)
102  CALL pack_same_rank(kmask,zdy1,zdy2)
103 !
104 DEALLOCATE(zx1 )
105 DEALLOCATE(zy1 )
106 DEALLOCATE(zdx1)
107 DEALLOCATE(zdy1)
108 !
109  CALL put_gridtype_ign(zgrid_par2,ilambert,zx2,zy2,zdx2,zdy2,0,0,zxall,zyall)
110 !
111 DEALLOCATE(zxall)
112 DEALLOCATE(zyall)
113 !
114 IF (opack) THEN
115  pgrid_par2(:) = zgrid_par2(:)
116 ELSE
117  kgrid_par2 = SIZE(zgrid_par2(:))
118 END IF
119 !
120 DEALLOCATE(zgrid_par2)
121 DEALLOCATE(zx2 )
122 DEALLOCATE(zy2 )
123 DEALLOCATE(zdx2)
124 DEALLOCATE(zdy2)
125 IF (lhook) CALL dr_hook('PACK_GRID_IGN',1,zhook_handle)
126 !-------------------------------------------------------------------------------
127 !
128 END SUBROUTINE pack_grid_ign
subroutine get_gridtype_ign(PGRID_PAR, KLAMBERT, KL, PX, PY, PDX, PDY, KDIMX, KDIMY, PXALL, PYALL)
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine pack_grid_ign(KMASK_SIZE, KMASK, KGRID_PAR1, PGRID_PAR1, KG
subroutine put_gridtype_ign(PGRID_PAR, KLAMBERT, PX, PY, PDX, PDY, KDIMX, KDIMY, PXALL, PYALL)