My Project
mod_bulk.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! Copyright (c) 2007, The University of Massachusetts Dartmouth
14 ! Produced at the School of Marine Science & Technology
15 ! Marine Ecosystem Dynamics Modeling group
16 ! All rights reserved.
17 !
18 ! FVCOM has been developed by the joint UMASSD-WHOI research team. For
19 ! details of authorship and attribution of credit please see the FVCOM
20 ! technical manual or contact the MEDM group.
21 !
22 !
23 ! This file is part of FVCOM. For details, see http://fvcom.smast.umassd.edu
24 ! The full copyright notice is contained in the file COPYRIGHT located in the
25 ! root directory of the FVCOM code. This original header must be maintained
26 ! in all distributed versions.
27 !
28 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
29 ! AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO,
30 ! THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
31 ! PURPOSE ARE DISCLAIMED.
32 !
33 !/---------------------------------------------------------------------------/
34 ! CVS VERSION INFORMATION
35 ! $Id$
36 ! $Name$
37 ! $Revision$
38 !/===========================================================================/
39 
40 MODULE mod_bulk
41  USE mod_prec
42  implicit none
43 
44 CONTAINS
45 
46 
47 
48  SUBROUTINE asimple_drag(spdx,spdy,strx,stry)
49  IMPLICIT NONE
50  REAL(SP),ALLOCATABLE, TARGET, INTENT(IN) :: SPDX(:),SPDY(:)
51  REAL(SP),ALLOCATABLE, TARGET, INTENT(INOUT) :: STRX(:),STRY(:)
52 
53  REAL(SP), POINTER :: SPDXP(:),SPDYP(:)
54  REAL(SP), POINTER :: STRXP(:),STRYP(:)
55 
56  spdxp => spdx
57  spdyp => spdy
58 
59  strxp => strx
60  stryp => stry
61 
62  CALL psimple_drag(spdxp,spdyp,strxp,stryp)
63 
64 
65  END SUBROUTINE asimple_drag
66 
67 
68 
69  SUBROUTINE psimple_drag(spdx,spdy,strx,stry)
70  IMPLICIT NONE
71  REAL(SP), POINTER,INTENT(IN) :: SPDX(:),SPDY(:)
72  REAL(SP), POINTER, INTENT(INOUT) :: STRX(:),STRY(:)
73  INTEGER :: I, N
74  REAL(SP) :: CD, WDS, TX, TY
75 
76 
77  IF(.not.Associated(spdx)) WRITE(6,*) "SIMPLE DRAG: SPDX is not associated"
78  IF(.not.Associated(spdy)) WRITE(6,*) "SIMPLE DRAG: SPDY is not associated"
79  IF(.not.Associated(strx)) WRITE(6,*) "SIMPLE DRAG: STRX is not associated"
80  IF(.not.Associated(stry)) WRITE(6,*) "SIMPLE DRAG: STRY is not associated"
81 
82  n = ubound(spdx,1)
83 
84 
85  IF(n /= ubound(spdy,1)) WRITE(6,*) "SIMPLE DRAG: MIS-MATCHED DIMENSIONS"
86  IF(n /= ubound(stry,1)) WRITE(6,*) "SIMPLE DRAG: MIS-MATCHED DIMENSIONS"
87  IF(n /= ubound(strx,1)) WRITE(6,*) "SIMPLE DRAG: MIS-MATCHED DIMENSIONS"
88 
89  DO i=1,n
90  tx = spdx(i)
91  ty = spdy(i)
92  wds=sqrt(tx*tx+ty*ty)
93  cd=1.2e-3
94  IF (wds >= 11.0_sp) cd=(0.49_sp+0.065_sp*wds)*1.e-3_sp
95  IF (wds >= 25.0_sp) cd=(0.49_sp+0.065_sp*25.0_sp)*1.e-3_sp
96 
97  strx(i) = 1.2_sp*cd*tx*wds
98  stry(i) = 1.2_sp*cd*ty*wds
99 
100  END DO
101 
102 
103  END SUBROUTINE psimple_drag
104 
105 
106 
107 END MODULE mod_bulk
subroutine psimple_drag(spdx, spdy, strx, stry)
Definition: mod_bulk.f90:70
subroutine asimple_drag(spdx, spdy, strx, stry)
Definition: mod_bulk.f90:49