source: CPL/oasis3/trunk/src/lib/scrip/src/rotations.F90 @ 1677

Last change on this file since 1677 was 1677, checked in by aclsce, 12 years ago

Imported oasis3 (tag ipslcm5a) from cvs server to svn server (igcmg project).

File size: 10.3 KB
Line 
1MODULE rotations
2!-----------------------------------------------------------------------
3
4  USE kinds_mod             ! defines common data types     
5  USE constants             ! defines common constants     
6  USE mod_parameter
7  USE mod_unit
8  USE mod_printing 
9  USE mod_unitncdf
10 
11  IMPLICIT NONE
12
13#include <netcdf.inc>
14 
15  REAL (KIND=dbl_kind), PARAMETER :: &
16     rp_deg2rad = pi/180.            ! Conversion from degrees to radians
17
18!
19!  This module contains necessary routines for transformations between
20!  the referentials Cartesian, spheric and streched spheric.
21!
22
23!  History:
24!  --------
25!  E. Rapaport     2004/03     Created
26!
27
28CONTAINS
29
30!-----------------------------------------------------------------------
31
32  SUBROUTINE angel(cd_grd_name, id_grd_size, &
33       rda_sin_alpha, rda_cos_alpha)
34
35    CHARACTER (LEN=8), INTENT(in) :: &
36         cd_grd_name     ! grid name
37         
38    INTEGER (KIND=int_kind), INTENT(in) :: &
39         id_grd_size     ! grid size
40 
41    CHARACTER(LEN=8) :: &
42         name_ang        ! name of the angle valew in grids.nc
43                             
44    REAL (KIND=dbl_kind), DIMENSION (:), ALLOCATABLE :: &
45         rla_alpha       ! the angel between the direction j in streched and the
46                         ! north-south in spheric coordonate system
47       
48    INTEGER (KIND=int_kind) :: &
49         il_stat, il_varid, il_vtype, &     ! netcdf variables
50         icount, ilenstr, i
51
52!RETURN VALUE:
53
54    REAL (KIND=dbl_kind), DIMENSION(id_grd_size), INTENT(out) :: &
55         rda_sin_alpha,&     ! the sinus and cosinus for the angel between the
56         rda_cos_alpha       ! direction j in streched and the north-south
57                             ! in spheric
58   
59! !DESCRIPTION:
60!
61!  This routine finds the cosinus and sinus of the angle between the
62!  north-south direction in a spheric referential and the direction
63!  of gridlines j in a streched spheric referential.
64!  If there is no angel information in file grids.nc we stop.
65!
66
67    IF (nlogprt .GE. 2) THEN
68        WRITE (UNIT = nulou,FMT = *) ' '
69        WRITE (UNIT = nulou,FMT = *) &
70           '           ROUTINE angel  -  Level ?'
71        WRITE (UNIT = nulou,FMT = *) ' '
72        CALL FLUSH(nulou)
73    ENDIF
74
75    IF (lncdfgrd) THEN
76       icount = ilenstr(cd_grd_name,jpeight)
77       name_ang = cd_grd_name(1:icount)//'.ang'
78
79       CALL hdlerr &
80            (NF_OPEN('grids.nc',NF_NOWRITE,nc_grdid),'angel')
81
82       il_stat = NF_INQ_VARID(nc_grdid, name_ang, il_varid)
83
84       IF (il_stat < 0) THEN
85          WRITE (UNIT = nulou,FMT = *) &
86               'File grids.nc contains no angle information,'
87          WRITE (UNIT = nulou,FMT = *) &
88               'OASIS will stop'       
89          STOP
90       ELSE IF (il_stat == 0) THEN
91!
92!** Get angle information from file grids.nc
93!
94          ALLOCATE(rla_alpha(id_grd_size))
95       
96          CALL hdlerr(NF_GET_VAR_DOUBLE &
97               (nc_grdid, il_varid, rla_alpha),'angel') 
98
99          rda_sin_alpha(:) = SIN(rp_deg2rad*rla_alpha(:))       
100          rda_cos_alpha(:) = COS(rp_deg2rad*rla_alpha(:))
101       
102          DEALLOCATE(rla_alpha)
103       END IF
104    ELSE
105       il_stat = -1
106    END IF
107
108       IF (nlogprt .GE. 2) THEN
109          WRITE (UNIT = nulou,FMT = *) ' '
110          WRITE (UNIT = nulou,FMT = *) &
111               '          --------- End of routine angel ---------'
112          CALL FLUSH (nulou)
113       ENDIF
114
115     END SUBROUTINE angel
116!
117!-----------------------------------------------------------------------
118!
119     SUBROUTINE loc2spher(cd_grd_name, id_grd_size, rda_trans)
120         
121       CHARACTER (LEN=8),INTENT(in) :: &
122            cd_grd_name      ! grid name     
123   
124       INTEGER (KIND=int_kind), INTENT(in) :: &
125            id_grd_size      ! grid size
126 
127       REAL (KIND=dbl_kind), DIMENSION(id_grd_size) :: &
128            rla_sin_alpha, &    ! the sinus and cosinus for the angel between the
129            rla_cos_alpha       ! direction j in streched and the north-south
130                                ! in spheric
131! !RETURN VALUE:
132
133       REAL (KIND=dbl_kind), DIMENSION(id_grd_size,2,2), INTENT(out) :: &
134            rda_trans
135     
136! !DESCRIPTION:
137!
138!  This routine finds the transformation matrix between a local stretched
139!  spheric referential and a regulier spheric referential.
140!
141
142       IF (nlogprt .GE. 2) THEN
143          WRITE (UNIT = nulou,FMT = *) ' '
144          WRITE (UNIT = nulou,FMT = *) &
145               '           ROUTINE loc2spher  -  Level ?'
146          CALL FLUSH(nulou)
147       ENDIF
148!
149!*Find the angle between the two referentials
150!
151       CALL angel(cd_grd_name, id_grd_size, &
152            rla_sin_alpha, rla_cos_alpha)           
153
154       rda_trans(:,1,1) =  rla_cos_alpha 
155       rda_trans(:,2,1) =  rla_sin_alpha
156       rda_trans(:,1,2) =  -rla_sin_alpha 
157       rda_trans(:,2,2) =  rla_cos_alpha
158       
159       IF (nlogprt .GE. 2) THEN
160          WRITE (UNIT = nulou,FMT = *) &
161               '          --------- End of routine loc2spher ---------'
162          WRITE (UNIT = nulou,FMT = *) ' '
163          CALL FLUSH(nulou)
164       ENDIF
165
166     END SUBROUTINE loc2spher
167!
168!-----------------------------------------------------------------------
169!
170     SUBROUTINE spher2loc(cd_grd_name, id_grd_size, rda_trans)
171     
172       CHARACTER (LEN=8),INTENT(in) :: &
173            cd_grd_name       ! grid name     
174   
175       INTEGER (KIND=int_kind), INTENT(in) :: &
176            id_grd_size       ! grid size
177
178       REAL (KIND=dbl_kind), DIMENSION(id_grd_size) :: &
179            rla_sin_alpha, &  ! the sinus and cosinus for the angel between the
180            rla_cos_alpha     ! direction j in streched and the north-south in spheric
181   
182!*RETURN VALUE:
183   
184       REAL (KIND=dbl_kind), DIMENSION(id_grd_size,3,3), INTENT(out) :: rda_trans
185     
186!*DESCRIPTION:
187!  Finds the transformation matrix between a spheric and a stretched
188!  spheric referential.
189!
190
191       IF (nlogprt .GE. 2) THEN
192          WRITE (UNIT = nulou,FMT = *) ' '
193          WRITE (UNIT = nulou,FMT = *) &
194           '           ROUTINE spher2loc  -  Level ?'
195          CALL FLUSH(nulou)
196       ENDIF
197!
198!*Find the angle between the two referentials
199!     
200       CALL angel(cd_grd_name, id_grd_size, &
201            rla_sin_alpha, rla_cos_alpha)         
202
203       rda_trans(:,1,1) =  rla_cos_alpha 
204       rda_trans(:,2,1) =  -rla_sin_alpha
205       rda_trans(:,1,2) = rla_sin_alpha
206       rda_trans(:,2,2) =  rla_cos_alpha
207
208       rda_trans(:,1,3) = 0.
209       rda_trans(:,2,3) = 0.
210       rda_trans(:,3,1) = 0.
211       rda_trans(:,3,2) = 0.
212       rda_trans(:,3,3) = 1.
213
214       IF (nlogprt .GE. 2) THEN
215          WRITE (UNIT = nulou,FMT = *) &
216               '          --------- End of routine spher2loc ---------'
217          WRITE (UNIT = nulou,FMT = *) ' '
218          CALL FLUSH(nulou)
219       ENDIF
220
221     END SUBROUTINE spher2loc   
222!
223!-----------------------------------------------------------------------
224!
225     SUBROUTINE spher2car(rda_grd_lon, rda_grd_lat, id_grd_size, rda_trans)
226
227       INTEGER (KIND=int_kind), INTENT(in) :: &
228            id_grd_size                    ! grid size
229   
230       REAL (KIND=dbl_kind), DIMENSION(id_grd_size),INTENT(in) :: &
231            rda_grd_lon, &                 ! grid longitudes
232            rda_grd_lat                    ! grid latitudes
233   
234       REAL (KIND=dbl_kind), DIMENSION(id_grd_size) :: &
235            rla_sin_lon, rla_cos_lon, &    ! sinus and cosinus for longitudes
236            rla_sin_lat, rla_cos_lat       ! sinus and cosinus for latitudes
237
238! !RETURN VALUE:
239 
240       REAL (KIND=dbl_kind), DIMENSION(id_grd_size,3,2), INTENT(out) :: rda_trans 
241   
242! !DESCRIPTION:
243!  Finds the rotation matrix between a spheric and cartesien referentails.
244!
245
246    IF (nlogprt .GE. 2) THEN
247        WRITE (UNIT = nulou,FMT = *) ' '
248        WRITE (UNIT = nulou,FMT = *) &
249           '           ROUTINE   - spher2car Level ?'
250        WRITE (UNIT = nulou,FMT = *) ' '
251        CALL FLUSH(nulou)
252    ENDIF
253
254    rla_sin_lon(:) = SIN(rda_grd_lon(:) * rp_deg2rad)
255    rla_cos_lon(:) = COS(rda_grd_lon(:) * rp_deg2rad)
256    rla_sin_lat(:) = SIN(rda_grd_lat(:) * rp_deg2rad)
257    rla_cos_lat(:) = COS(rda_grd_lat(:) * rp_deg2rad)
258
259    rda_trans(:,1,1) = -rla_sin_lon(:)
260    rda_trans(:,2,1) = -rla_sin_lat(:) * rla_cos_lon(:)
261    rda_trans(:,1,2) =  rla_cos_lon(:)
262    rda_trans(:,2,2) = -rla_sin_lat(:) * rla_sin_lon(:)
263    rda_trans(:,3,1) = rla_cos_lon(:) * rla_cos_lat(:) 
264    rda_trans(:,3,2) = rla_cos_lat(:) * rla_sin_lon(:)
265 
266    IF (nlogprt .GE. 2) THEN
267        WRITE (UNIT = nulou,FMT = *) ' '
268        WRITE (UNIT = nulou,FMT = *) &
269           '          --------- End of routine spher2car ---------'
270        CALL FLUSH (nulou)
271    ENDIF
272
273  END SUBROUTINE spher2car
274!
275!-----------------------------------------------------------------------
276!
277  SUBROUTINE car2spher(rda_grd_lon, rda_grd_lat, id_grd_size, rda_trans)
278
279    INTEGER (KIND=int_kind), INTENT(in) :: &
280         id_grd_size                    ! grid size
281   
282    REAL (KIND=dbl_kind), DIMENSION(id_grd_size),INTENT(in) :: &
283         rda_grd_lon, &                 ! grid longitudes
284         rda_grd_lat                    ! grid latitudes
285
286    REAL (KIND=dbl_kind), DIMENSION(id_grd_size) :: &
287         rla_sin_lon, rla_cos_lon, &    ! sinus and cosinu for longitudes
288         rla_sin_lat, rla_cos_lat       ! sinus and cosinu for latitudes
289
290! !RETURN VALUE:
291
292    REAL (KIND=dbl_kind), DIMENSION(id_grd_size,3,3), INTENT(out) :: rda_trans
293   
294! !DESCRIPTION:
295!  Finds the rotation matrix between a cartesien and a spheric referential.
296!
297 
298    IF (nlogprt .GE. 2) THEN
299        WRITE (UNIT = nulou,FMT = *) ' '
300        WRITE (UNIT = nulou,FMT = *) &
301           '           ROUTINE   - car2spher Level ?'
302        WRITE (UNIT = nulou,FMT = *) ' '
303        CALL FLUSH(nulou)
304    ENDIF
305 
306    rla_sin_lon(:) = SIN(rda_grd_lon(:) * rp_deg2rad)
307    rla_cos_lon(:) = COS(rda_grd_lon(:) * rp_deg2rad)
308    rla_sin_lat(:) = SIN(rda_grd_lat(:) * rp_deg2rad)
309    rla_cos_lat(:) = COS(rda_grd_lat(:) * rp_deg2rad)
310   
311    rda_trans(:,1,1) =  -rla_sin_lon(:)
312    rda_trans(:,2,1) =   rla_cos_lon(:) 
313    rda_trans(:,3,1) =   0.
314    rda_trans(:,1,2) =  -rla_sin_lat(:) * rla_cos_lon(:)
315    rda_trans(:,2,2) =  -rla_sin_lat(:) * rla_sin_lon(:) 
316    rda_trans(:,3,2) =   rla_cos_lat(:)
317    rda_trans(:,1,3) =   rla_cos_lat(:) * rla_cos_lon(:)
318    rda_trans(:,2,3) =   rla_cos_lat(:) * rla_sin_lon(:)
319    rda_trans(:,3,3) =   rla_sin_lat(:)
320
321    IF (nlogprt .GE. 2) THEN
322        WRITE (UNIT = nulou,FMT = *) ' '
323        WRITE (UNIT = nulou,FMT = *) &
324           '          --------- End of routine car2spher ---------'
325        CALL FLUSH (nulou)
326    ENDIF
327
328  END SUBROUTINE car2spher
329
330
331END MODULE rotations
Note: See TracBrowser for help on using the repository browser.