SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pack_grid_lonlat_reg.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_lonlat_reg(KMASK_SIZE,KMASK,KGRID_PAR1,PGRID_PAR1,KGRID_PAR2,OPACK,PGRID_PAR2)
7 ! ##############################################################
8 !
9 !!**** *PACK_GRID_LONLAT_REG* 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 :: zlonmin ! minimum longitude (degrees)
59 REAL :: zlonmax ! maximum longitude (degrees)
60 REAL :: zlatmin ! minimum latitude (degrees)
61 REAL :: zlatmax ! maximum latitude (degrees)
62 INTEGER :: ilon ! number of points in longitude
63 INTEGER :: ilat ! number of points in latitude
64 INTEGER :: il ! number of points used
65 REAL, DIMENSION(:), ALLOCATABLE :: zlat1 ! latitude of all grid points
66 REAL, DIMENSION(:), ALLOCATABLE :: zlon1 ! longitude of all grid points
67 REAL, DIMENSION(:), ALLOCATABLE :: zlat2 ! latitude of subset of grid points
68 REAL, DIMENSION(:), ALLOCATABLE :: zlon2 ! longitude of subset of grid points
69 
70 !
71 REAL, DIMENSION(:), POINTER :: zgrid_par2 ! parameters of output grid
72 REAL(KIND=JPRB) :: zhook_handle
73 !----------------------------------------------------------------------------
74 !
75 !* 1. Computes grid parameters
76 ! ------------------------
77 !
78 IF (lhook) CALL dr_hook('PACK_GRID_LONLAT_REG',0,zhook_handle)
79  CALL get_gridtype_lonlat_reg(pgrid_par1,zlonmin,zlonmax, &
80  zlatmin,zlatmax,ilon,ilat, il )
81 ALLOCATE(zlat1(il))
82 ALLOCATE(zlon1(il))
83 !
84  CALL get_gridtype_lonlat_reg(pgrid_par1,plon=zlon1,plat=zlat1)
85 !----------------------------------------------------------------------------
86 !
87 !* 2. Packs latitude and longitude arrays
88 ! -----------------------------------
89 !
90 !
91 ALLOCATE(zlat2(kmask_size))
92 ALLOCATE(zlon2(kmask_size))
93 !
94  CALL pack_same_rank(kmask,zlat1,zlat2)
95  CALL pack_same_rank(kmask,zlon1,zlon2)
96 !
97 DEALLOCATE(zlat1)
98 DEALLOCATE(zlon1)
99 
100 !----------------------------------------------------------------------------
101 !
102 !* 3. Stores data in new grid vector
103 ! ------------------------------
104 !
105  CALL put_gridtype_lonlat_reg(zgrid_par2,zlonmin,zlonmax, &
106  zlatmin,zlatmax,ilon,ilat,kmask_size,zlon2,zlat2)
107 
108 DEALLOCATE(zlat2)
109 DEALLOCATE(zlon2)
110 !----------------------------------------------------------------------------
111 !
112 IF (opack) THEN
113  pgrid_par2(:) = zgrid_par2(:)
114 ELSE
115  kgrid_par2 = SIZE(zgrid_par2(:))
116 END IF
117 !
118 DEALLOCATE(zgrid_par2)
119 IF (lhook) CALL dr_hook('PACK_GRID_LONLAT_REG',1,zhook_handle)
120 !-------------------------------------------------------------------------------
121 !
122 END SUBROUTINE pack_grid_lonlat_reg
subroutine pack_grid_lonlat_reg(KMASK_SIZE, KMASK, KGRID_PAR1, PGRID_PAR1, KGRID_PAR2, OPACK, PGRID_PAR2)
subroutine get_gridtype_lonlat_reg(PGRID_PAR, PLONMIN, PLONMAX, PLATMIN, PLATMAX, KLON, KLAT, KL, PLON, PLAT)
subroutine put_gridtype_lonlat_reg(PGRID_PAR, PLONMIN, PLONMAX, PLATMIN, PLATMAX, KLON, KLAT, KL, PLON, PLAT)