SURFEX v8.1
General documentation of Surfex
prep_grid_gauss.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 prep_grid_gauss (&
7  HFILETYPE,HINTERP_TYPE,KNI)
8 ! ##########################################################################
9 !
10 !!**** *PREP_GRID_GAUSS* - reads EXTERNALIZED Surface grid.
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! V. Masson
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 06/2003
37 !! M. Jidane Nov 2013 : correct allocation of NINLO and reading of INLOPA
38 !! F. Taillefer Dec 2013 : debug estimation of XILO2
39 !-------------------------------------------------------------------------------
40 !
41 !* 0. DECLARATIONS
42 ! ------------
43 !
44 !
45 !
46 !
48 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1. Declaration of arguments
58 ! ------------------------
59 !
60 !
61 !
62  CHARACTER(LEN=6), INTENT(IN) :: HFILETYPE ! file type
63  CHARACTER(LEN=6), INTENT(OUT) :: HINTERP_TYPE ! Grid type
64 INTEGER, INTENT(OUT) :: KNI ! number of points
65 !
66 !* 0.2 Declaration of local variables
67 ! ------------------------------
68 !
69  CHARACTER(LEN=12) :: YRECFM ! Name of the article to be read
70 INTEGER :: IRESP
71 !
72 !
73 REAL, DIMENSION(:), ALLOCATABLE :: ZLAT ! latitudes
74 REAL, DIMENSION(:), ALLOCATABLE :: ZW ! work array
75 !
76 INTEGER :: JL, ICPT ! loop counter
77 INTEGER :: INLATI ! number of pseudo-latitudes
78 INTEGER :: INLATI2 ! number of half pseudo-latitudes
79 REAL :: ZLAPO ! latitude of the rotated pole (deg)
80 REAL :: ZLOPO ! longitude of the rotated pole (deg)
81 REAL :: ZCODIL ! stretching factor (must be greater than or equal to 1)
82 INTEGER, DIMENSION(:), ALLOCATABLE :: INLOPA ! number of pseudo-longitudes on each
83  ! pseudo-latitude circle
84 REAL(KIND=JPRB) :: ZHOOK_HANDLE
85 !
86 !-----------------------------------------------------------------------
87 IF (lhook) CALL dr_hook('PREP_GRID_GAUSS',0,zhook_handle)
88 !-----------------------------------------------------------------------
89 !
90 !* 1 Projection
91 ! ----------
92 !
93 yrecfm = 'LAPO'
94  CALL read_surf(hfiletype,yrecfm,zlapo,iresp)
95 yrecfm = 'LOPO'
96  CALL read_surf(hfiletype,yrecfm,zlopo,iresp)
97 yrecfm = 'CODIL'
98  CALL read_surf(hfiletype,yrecfm,zcodil,iresp)
99 !
100 !-----------------------------------------------------------------------
101 !
102 !* 2 Grid
103 ! ----
104 !
105 yrecfm = 'NLATI'
106  CALL read_surf(hfiletype,yrecfm,inlati,iresp)
107 !
108 IF (ALLOCATED(inlopa)) DEALLOCATE(inlopa)
109 ALLOCATE(inlopa(inlati))
110 IF (ALLOCATED(ninlo)) DEALLOCATE(ninlo)
111 ALLOCATE(ninlo(inlati))
112 yrecfm = 'NLOPA'
113  CALL read_surf(hfiletype,yrecfm,inlopa,iresp,hdir='-')
114 !
115 kni = sum(inlopa)
116 !
117 ALLOCATE(zlat(kni))
118 ! CALL READ_SURF(HFILETYPE,'LATGAUSS',ZLAT(:),IRESP,HDIR='-')
119  CALL read_surf(hfiletype,'LAT_G_XY',zlat(:),iresp,hdir='-')
120 !
121 IF (ALLOCATED(xilatarray)) DEALLOCATE(xilatarray)
122 ALLOCATE(xilatarray(inlati))
123 xilatarray(1) = zlat(1)
124 icpt = 1
125 DO jl = 2,kni
126  IF (zlat(jl)/=zlat(jl-1)) THEN
127  icpt = icpt + 1
128  xilatarray(icpt) = zlat(jl)
129  ENDIF
130 ENDDO
131 !
132 DEALLOCATE(zlat)
133 !-----------------------------------------------------------------------
134 !
135 !* 3 Computes additional quantities used in interpolation
136 ! ----------------------------------------------------
137 !
138 inlati2 = nint(REAL(inlati)/2.0)
139 ninla = inlati
140 nilen = kni
141 xlop = zlopo
142 xlap = zlapo
143 xcoef = zcodil
144 !
145 ninlo(:) = inlopa(:)
146 !
147 !* type of transform
148 IF (zlapo>89.99 .AND. abs(zlopo)<0.00001) THEN
149  lrotpole = .false.
150 ELSE
151  lrotpole = .true.
152 ENDIF
153 !
154 !XILA1=90.0*(1.0-1.0/(REAL(INLATI)))
155 !XILA2=-90.0*(1.0-1.0/(REAL(INLATI)))
156 xila1 = xilatarray(1)
157 xila2 = xilatarray(inlati)
158 xilo1=0.0
159 xilo2=360.0*(REAL(inlopa(inlati2))-1.0)/REAL(INLOPA(inlati2))
160 !
161 hinterp_type = 'HORIBL'
162 !-----------------------------------------------------------------------
163 IF (lhook) CALL dr_hook('PREP_GRID_GAUSS',1,zhook_handle)
164 !-----------------------------------------------------------------------
165 !
166 END SUBROUTINE prep_grid_gauss
integer, parameter jprb
Definition: parkind1.F90:32
integer, dimension(:), allocatable ninlo
subroutine prep_grid_gauss(HFILETYPE, HINTERP_TYPE, KNI)
real, dimension(:), allocatable xilatarray
intent(out) overrides sub arrays one Sort by the least significant key first sum(iindex(1:n))
logical lhook
Definition: yomhook.F90:15