SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pack_grid_lonlat_rot.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_rot(KMASK_SIZE,KMASK,KGRID_PAR1,PGRID_PAR1,KGRID_PAR2,OPACK,PGRID_PAR2)
7 ! ##############################################################
8 !
9 !!**** *PACK_GRID_LONLAT_ROT* packs the grid definition vector
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !! METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !! AUTHOR
21 !! ------
22 !! P. Samuelsson SMHI
23 !!
24 !! MODIFICATIONS
25 !! -------------
26 !! Original 12/2012
27 !!
28 !----------------------------------------------------------------------------
29 !
30 !* 0. DECLARATION
31 ! -----------
32 !
35 !
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 !* 0.1 Declaration of arguments
43 ! ------------------------
44 !
45 INTEGER, INTENT(IN) :: kmask_size ! size of mask
46 INTEGER, DIMENSION(KMASK_SIZE), INTENT(IN) :: kmask ! mask used
47 INTEGER, INTENT(IN) :: kgrid_par1 ! size of input grid vector
48 REAL, DIMENSION(KGRID_PAR1), INTENT(IN) :: pgrid_par1 ! parameters of input grid
49 INTEGER, INTENT(INOUT) :: kgrid_par2 ! size of output grid vector
50 LOGICAL, INTENT(IN) :: opack ! flag to pack the grid vector
51 REAL, DIMENSION(KGRID_PAR2), INTENT(OUT) :: pgrid_par2 ! parameters of output grid
52 !
53 !* 0.2 Declaration of other local variables
54 ! ------------------------------------
55 !
56 REAL :: zwest ! West longitude in rotated grid (degrees)
57 REAL :: zsouth ! South latitude in rotated grid (degrees)
58 REAL :: zdlon ! Longitudal grid spacing (degrees)
59 REAL :: zdlat ! Latitudal grid spacing (degrees)
60 REAL :: zpolon ! Longitude of rotated pole (degrees)
61 REAL :: zpolat ! Latitude of rotated pole (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_ROT',0,zhook_handle)
79  CALL get_gridtype_lonlat_rot(pgrid_par1, &
80  zwest,zsouth,zdlon,zdlat,zpolon,zpolat, &
81  ilon,ilat, il )
82 ALLOCATE(zlat1(il))
83 ALLOCATE(zlon1(il))
84 !
85  CALL get_gridtype_lonlat_rot(pgrid_par1,plon=zlon1,plat=zlat1)
86 !----------------------------------------------------------------------------
87 !
88 !* 2. Packs latitude and longitude arrays
89 ! -----------------------------------
90 !
91 !
92 ALLOCATE(zlat2(kmask_size))
93 ALLOCATE(zlon2(kmask_size))
94 !
95  CALL pack_same_rank(kmask,zlat1,zlat2)
96  CALL pack_same_rank(kmask,zlon1,zlon2)
97 !
98 DEALLOCATE(zlat1)
99 DEALLOCATE(zlon1)
100 
101 !----------------------------------------------------------------------------
102 !
103 !* 3. Stores data in new grid vector
104 ! ------------------------------
105 !
106  CALL put_gridtype_lonlat_rot(zgrid_par2, &
107  zwest,zsouth,zdlon,zdlat,zpolon,zpolat, &
108  ilon,ilat,kmask_size,zlon2,zlat2 )
109 
110 DEALLOCATE(zlat2)
111 DEALLOCATE(zlon2)
112 !----------------------------------------------------------------------------
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 IF (lhook) CALL dr_hook('PACK_GRID_LONLAT_ROT',1,zhook_handle)
122 !-------------------------------------------------------------------------------
123 !
124 END SUBROUTINE pack_grid_lonlat_rot
subroutine get_gridtype_lonlat_rot(PGRID_PAR, PWEST, PSOUTH, PDLON, PDLAT, PPOLON, PPOLAT, KLON, KLAT, KL, PLON, PLAT)
subroutine pack_grid_lonlat_rot(KMASK_SIZE, KMASK, KGRID_PAR1, PGRID_PAR1, KGRID_PAR2, OPACK, PGRID_PAR2)
subroutine put_gridtype_lonlat_rot(PGRID_PAR, PWEST, PSOUTH, PDLON, PDLAT, PPOLON, PPOLAT, KLON, KLAT, KL, PLON, PLAT)