source: trunk/MESOSCALE_DEV/SRC/ARWpost/src/module_calc_wdir.f90 @ 524

Last change on this file since 524 was 207, checked in by aslmd, 14 years ago

MESOSCALE: A GENERAL CLEAN-UP FOLLOWING UPDATING THE USER MANUAL. EVERYTHING ESSENTIAL IS IN MESOSCALE (much lighter than before). EVERYTHING FOR DEVELOPPERS OR EXPERTS IS IN MESOSCALE_DEV.

File size: 823 bytes
Line 
1!! Diagnostics: Wind Direction
2
3MODULE module_calc_wdir
4
5  CONTAINS
6  SUBROUTINE calc_wdir(SCR, cname, cdesc, cunits, i3dflag)
7
8  USE constants_module
9  USE module_model_basics
10
11  !Arguments
12  real, pointer, dimension(:,:,:)                 :: SCR
13  character (len=128)                             :: cname, cdesc, cunits
14
15  !Local
16  integer                                         :: i3dflag
17 
18
19  IF ( i3dflag == 1 ) THEN
20    SCR      = 270. - ATAN2(VVV,UUU) * DEG_PER_RAD
21    cname    = "wdir"
22    cdesc    = "Wind Direction"
23  ELSE
24    SCR(:,:,1)      = 270. - ATAN2(V10(:,:),U10(:,:)) * DEG_PER_RAD
25    cname    = "wd10"
26    cdesc    = "Wind Direction at 10 M"
27  ENDIF
28 
29  WHERE (SCR .gt. 360. )
30    SCR    = SCR - 360.
31  END WHERE
32
33  cunits   = "Degrees"
34 
35  END SUBROUTINE calc_wdir
36
37END MODULE module_calc_wdir
38
Note: See TracBrowser for help on using the repository browser.