| 1 | MODULE module_wind_generic |
|---|
| 2 | |
|---|
| 3 | IMPLICIT NONE |
|---|
| 4 | |
|---|
| 5 | TYPE windturbine_specs |
|---|
| 6 | INTEGER id ! grid id |
|---|
| 7 | REAL lat, lon ! lat/lon of the individual turbine |
|---|
| 8 | REAL i, j ! x and y coords of turbines (set by packages themselves) |
|---|
| 9 | REAL hubheight ! hieght of the turbine hub |
|---|
| 10 | REAL diameter ! diameter of the rotor |
|---|
| 11 | REAL stdthrcoef ! standing thrust coefficient |
|---|
| 12 | REAL power ! turbine power in MW |
|---|
| 13 | REAL cutinspeed ! cut-in speed |
|---|
| 14 | REAL cutoutspeed ! cut-out speed |
|---|
| 15 | END TYPE windturbine_specs |
|---|
| 16 | |
|---|
| 17 | TYPE(windturbine_specs), TARGET, ALLOCATABLE, DIMENSION(:) :: windturbines |
|---|
| 18 | INTEGER :: nwindturbines |
|---|
| 19 | |
|---|
| 20 | INTEGER, PARAMETER :: WIND_TURBINES_OFF = 0 |
|---|
| 21 | INTEGER, PARAMETER :: WIND_TURBINES_IDEAL = 1 |
|---|
| 22 | INTEGER, PARAMETER :: WIND_TURBINES_FROMLIST = 2 |
|---|
| 23 | |
|---|
| 24 | INTEGER windspec |
|---|
| 25 | |
|---|
| 26 | LOGICAL , EXTERNAL :: wrf_dm_on_monitor |
|---|
| 27 | |
|---|
| 28 | CONTAINS |
|---|
| 29 | |
|---|
| 30 | SUBROUTINE read_windturbines_in |
|---|
| 31 | ! Check the namelist variable nl_get_windturbines_spec. If it is set to none, |
|---|
| 32 | ! which is the default value, then do nothing. If it is set to ideal, then |
|---|
| 33 | ! a wind scheme is active but no extra information beyond what is in the namelist |
|---|
| 34 | ! is needed. If it is set to the name of a file, read the file to get position |
|---|
| 35 | ! and characteristics of each turbine and store that in a datastructure here |
|---|
| 36 | ! (the array turbinespec) that the parameterizations can refer to when initializing |
|---|
| 37 | ! themselves. |
|---|
| 38 | |
|---|
| 39 | IMPLICIT NONE |
|---|
| 40 | ! Local |
|---|
| 41 | CHARACTER*256 fname, message |
|---|
| 42 | CHARACTER*512 inline |
|---|
| 43 | INTEGER i,istat |
|---|
| 44 | INTEGER id |
|---|
| 45 | INTEGER n,lineno,ig,jg |
|---|
| 46 | REAL lat,lon,hubheight,diameter,stdthrcoef,power,cutinspeed,cutoutspeed |
|---|
| 47 | ! |
|---|
| 48 | CALL nl_get_windturbines_spec( 1, fname ) |
|---|
| 49 | windspec = WIND_TURBINES_OFF |
|---|
| 50 | IF ( TRIM(fname) .EQ. "none" ) THEN |
|---|
| 51 | RETURN |
|---|
| 52 | ELSE IF ( TRIM(fname) .EQ. "ideal" ) THEN |
|---|
| 53 | ! get the turbine specs from the namelist and initialize in |
|---|
| 54 | ! the specific turbine parameterization |
|---|
| 55 | windspec = WIND_TURBINES_IDEAL |
|---|
| 56 | ELSE |
|---|
| 57 | !info is contained in a file named by fname |
|---|
| 58 | !read in and distributed between processors here (if dmpar or dm+sm) but |
|---|
| 59 | !the parameterizations themselves must initialize themselves |
|---|
| 60 | IF ( wrf_dm_on_monitor() ) THEN |
|---|
| 61 | OPEN(file=TRIM(fname),unit=19,FORM='FORMATTED',STATUS='OLD',IOSTAT=istat) |
|---|
| 62 | IF ( istat .EQ. 0 ) THEN |
|---|
| 63 | ! first time count things up |
|---|
| 64 | n = 0 |
|---|
| 65 | DO WHILE (.true.) |
|---|
| 66 | READ(19,'(A256)',END=30)inline |
|---|
| 67 | IF ( index(inline,'!') .EQ. 0 ) n = n + 1 |
|---|
| 68 | ENDDO |
|---|
| 69 | 30 CONTINUE |
|---|
| 70 | nwindturbines = n |
|---|
| 71 | IF ( .NOT. ALLOCATED(windturbines) ) ALLOCATE(windturbines(nwindturbines)) |
|---|
| 72 | REWIND(19) |
|---|
| 73 | i = 1 |
|---|
| 74 | lineno = 0 |
|---|
| 75 | DO WHILE (.true.) |
|---|
| 76 | lineno = lineno + 1 |
|---|
| 77 | READ(19,'(A256)',END=120)inline |
|---|
| 78 | IF ( i .LE. nwindturbines .AND. index(inline,'!') .EQ. 0 ) THEN |
|---|
| 79 | READ(inline,*,ERR=130)id,lat,lon,hubheight,diameter,stdthrcoef,power,cutinspeed,cutoutspeed |
|---|
| 80 | windturbines(i)%id = id |
|---|
| 81 | windturbines(i)%lat = lat |
|---|
| 82 | windturbines(i)%lon = lon |
|---|
| 83 | windturbines(i)%i = -999 ! set to invalid |
|---|
| 84 | windturbines(i)%j = -999 ! set to invalid |
|---|
| 85 | windturbines(i)%hubheight = hubheight |
|---|
| 86 | windturbines(i)%diameter = diameter |
|---|
| 87 | windturbines(i)%stdthrcoef = stdthrcoef |
|---|
| 88 | windturbines(i)%power = power |
|---|
| 89 | windturbines(i)%cutinspeed = cutinspeed |
|---|
| 90 | windturbines(i)%cutoutspeed = cutoutspeed |
|---|
| 91 | i = i + 1 |
|---|
| 92 | ENDIF |
|---|
| 93 | ENDDO |
|---|
| 94 | 120 CONTINUE |
|---|
| 95 | CLOSE(19) |
|---|
| 96 | GOTO 150 |
|---|
| 97 | 130 CONTINUE |
|---|
| 98 | CLOSE(19) ! in case of error, close the unit |
|---|
| 99 | istat = 150150 |
|---|
| 100 | GOTO 150 |
|---|
| 101 | ENDIF |
|---|
| 102 | ENDIF |
|---|
| 103 | 150 CONTINUE |
|---|
| 104 | CALL wrf_dm_bcast_integer(istat,1) |
|---|
| 105 | IF ( istat .NE. 0 ) THEN |
|---|
| 106 | WRITE(message,*)'Unable to open or read ',TRIM(fname),'. Proceeding without wind-turbine parameterization.' |
|---|
| 107 | CALL wrf_message(message) |
|---|
| 108 | IF ( istat .EQ. 150150 ) THEN |
|---|
| 109 | WRITE(message,*)'Perhaps bad syntax at line ',lineno,' of ',TRIM(fname) |
|---|
| 110 | CALL wrf_message(message) |
|---|
| 111 | ENDIF |
|---|
| 112 | IF ( ALLOCATED(windturbines) ) DEALLOCATE(windturbines) |
|---|
| 113 | RETURN |
|---|
| 114 | ENDIF |
|---|
| 115 | CALL wrf_dm_bcast_integer(nwindturbines,1) |
|---|
| 116 | IF ( .NOT. wrf_dm_on_monitor() ) THEN |
|---|
| 117 | IF ( .NOT. ALLOCATED(windturbines) ) ALLOCATE(windturbines(nwindturbines)) |
|---|
| 118 | ENDIF |
|---|
| 119 | DO i = 1, nwindturbines |
|---|
| 120 | CALL wrf_dm_bcast_integer(windturbines(i)%id,1) |
|---|
| 121 | CALL wrf_dm_bcast_real(windturbines(i)%lat,1) |
|---|
| 122 | CALL wrf_dm_bcast_real(windturbines(i)%lon,1) |
|---|
| 123 | CALL wrf_dm_bcast_real(windturbines(i)%hubheight,1) |
|---|
| 124 | CALL wrf_dm_bcast_real(windturbines(i)%diameter,1) |
|---|
| 125 | CALL wrf_dm_bcast_real(windturbines(i)%stdthrcoef,1) |
|---|
| 126 | CALL wrf_dm_bcast_real(windturbines(i)%power,1) |
|---|
| 127 | CALL wrf_dm_bcast_real(windturbines(i)%cutinspeed,1) |
|---|
| 128 | CALL wrf_dm_bcast_real(windturbines(i)%cutoutspeed,1) |
|---|
| 129 | ENDDO |
|---|
| 130 | windspec = WIND_TURBINES_FROMLIST |
|---|
| 131 | RETURN |
|---|
| 132 | ENDIF |
|---|
| 133 | END SUBROUTINE read_windturbines_in |
|---|
| 134 | |
|---|
| 135 | SUBROUTINE init_module_wind_generic |
|---|
| 136 | IMPLICIT NONE |
|---|
| 137 | CALL read_windturbines_in |
|---|
| 138 | END SUBROUTINE init_module_wind_generic |
|---|
| 139 | |
|---|
| 140 | END MODULE module_wind_generic |
|---|