Changeset 2274 in lmdz_wrf for trunk/tools/module_ForDiagnostics.f90
- Timestamp:
- Dec 28, 2018, 3:35:45 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/tools/module_ForDiagnostics.f90
r2260 r2274 16 16 ! compute_cape_afwa4D: Subroutine to use WRF phys/module_diag_afwa.F `buyoancy' subroutine to compute 17 17 ! CAPE, CIN, ZLFC, PLFC, LI 18 ! compute_cellbnds: Subroutine to compute cellboundaries using wind-staggered lon, lats as 19 ! intersection of their related parallels and meridians 18 20 ! compute_cllmh4D3: Computation of low, medium and high cloudiness from a 4D CLDFRA and pressure being 19 21 ! 3rd dimension the z-dim … … 1051 1053 END SUBROUTINE compute_range_faces 1052 1054 1055 SUBROUTINE compute_cellbnds(dx, dy, sdx, sdy, ulon, ulat, vlon, vlat, xbnds, ybnds) 1056 ! Subroutine to compute cellboundaries using wind-staggered lon, lats as intersection of their related 1057 ! parallels and meridians 1058 1059 IMPLICIT NONE 1060 1061 INTEGER, INTENT(in) :: dx, dy, sdx, sdy 1062 REAL(r_k), DIMENSION(sdx, dy), INTENT(in) :: ulon, ulat 1063 REAL(r_k), DIMENSION(dx, sdy), INTENT(in) :: vlon, vlat 1064 REAL(r_k), DIMENSION(dx, dy, 4), INTENT(out) :: xbnds, ybnds 1065 1066 ! Local 1067 INTEGER :: i,j,iv 1068 INTEGER :: ix,ex,iy,ey 1069 CHARACTER(len=2), DIMENSION(4) :: Svertex 1070 INTEGER, DIMENSION(4,2,2,2) :: indices 1071 REAL(r_k), DIMENSION(2) :: ptintsct 1072 REAL(r_k), DIMENSION(2,2) :: merid, paral 1073 LOGICAL :: intsct 1074 1075 !!!!!!! Variables 1076 ! dx, dy: un-staggered dimensions 1077 ! sdx, sdy: staggered dimensions 1078 ! ulon, ulat: x-wind staggered longitudes and latitudes 1079 ! vlon, vlat: y-wind staggered longitudes and latitudes 1080 ! xbnds, ybnds: x and y cell boundaries 1081 1082 fname = 'compute_cellbnds' 1083 1084 ! Indices to use indices[SW/NW/NE/SE, m/p, x/y, i/e] 1085 Svertex = (/ 'SW', 'NW', 'NE', 'SE' /) 1086 1087 ! SW 1088 indices(1,1,1,1) = 0 1089 indices(1,1,1,2) = 0 1090 indices(1,1,2,1) = -1 1091 indices(1,1,2,2) = 0 1092 indices(1,2,1,1) = -1 1093 indices(1,2,1,2) = 0 1094 indices(1,2,2,1) = -1 1095 indices(1,2,2,2) = -1 1096 ! NW 1097 indices(2,1,1,1) = 0 1098 indices(2,1,1,2) = 0 1099 indices(2,1,2,1) = 0 1100 indices(2,1,2,2) = 1 1101 indices(2,2,1,1) = -1 1102 indices(2,2,1,2) = 0 1103 indices(2,2,2,1) = 1 1104 indices(2,2,2,2) = 1 1105 ! NE 1106 indices(3,1,1,1) = 1 1107 indices(3,1,1,2) = 1 1108 indices(3,1,2,1) = 0 1109 indices(3,1,2,2) = 1 1110 indices(3,2,1,1) = 0 1111 indices(3,2,1,2) = 1 1112 indices(3,2,2,1) = 1 1113 indices(3,2,2,2) = 1 1114 ! SE 1115 indices(4,1,1,1) = 1 1116 indices(4,1,1,2) = 1 1117 indices(4,1,2,1) = -1 1118 indices(4,1,2,2) = 0 1119 indices(4,2,1,1) = 0 1120 indices(4,2,1,2) = 1 1121 indices(4,2,2,1) = -1 1122 indices(4,2,2,2) = -1 1123 1124 DO i=1,dx 1125 DO j=1,dy 1126 DO iv=1,4 1127 1128 ix = MAX(i+indices(iv,1,1,1),1) 1129 !ex = MIN(i+indices(iv,1,1,2),dx) 1130 ex = i+indices(iv,1,1,2) 1131 iy = MAX(j+indices(iv,1,2,1),1) 1132 ey = MIN(j+indices(iv,1,2,2),dy) 1133 1134 merid(1,1) = ulon(ix,iy) 1135 merid(1,2) = ulat(ix,iy) 1136 merid(2,1) = ulon(ex,ey) 1137 merid(2,2) = ulat(ex,ey) 1138 1139 ix = MAX(i+indices(iv,2,1,1),1) 1140 ex = MIN(i+indices(iv,2,1,2),dx) 1141 iy = MAX(j+indices(iv,2,2,1),1) 1142 !ey = MIN(i+indices(iv,2,2,2),dy) 1143 ey = j+indices(iv,2,2,2) 1144 paral(1,1) = vlon(ix,iy) 1145 paral(1,2) = vlat(ix,iy) 1146 paral(2,1) = vlon(ex,ey) 1147 paral(2,2) = vlat(ex,ey) 1148 1149 CALL intersection_2Dlines(merid, paral, intsct, ptintsct) 1150 IF (.NOT.intsct) THEN 1151 msg = 'not interection found for ' // Svertex(iv) // ' vertex' 1152 CALL ErrMsg(msg, fname, -1) 1153 END IF 1154 xbnds(i,j,iv) = ptintsct(1) 1155 ybnds(i,j,iv) = ptintsct(2) 1156 END DO 1157 END DO 1158 END DO 1159 1160 END SUBROUTINE 1161 1053 1162 SUBROUTINE compute_Koeppen_Geiger_climates(dx, dy, dt, pr, tas, climatesI, climatesS, climlegend) 1054 1163 ! Subroutine to compute the Koeppen-Geiger climates after:
Note: See TracChangeset
for help on using the changeset viewer.