Changeset 2387 in lmdz_wrf for trunk/tools/module_ForDiagnostics.f90


Ignore:
Timestamp:
Mar 11, 2019, 11:40:11 AM (6 years ago)
Author:
lfita
Message:

Adding:

  • `tws': Wet Bulb temperature after Stull, 2011
File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/tools/module_ForDiagnostics.f90

    r2345 r2387  
    3535! compute_psl_ecmwf: Compute sea level pressure using ECMWF method following Mats Hamrud and Philippe Courtier [Pa]
    3636! compute_range_faces: Subroutine to compute faces [uphill, valleys, downhill] of a mountain range along a given face
     37! compute_tws_RK[1/2/3/4]: Subroutine to compute Wet Bulb temperature of 1/2/3/4D series of values
    3738! compute_vertint1D: Subroutine to vertically integrate a 1D variable in any vertical coordinates
    3839! compute_zint4D: Subroutine to vertically integrate a 4D variable in any vertical coordinates
     
    845846! Subroutine to compute fog: qcloud + qice /= 0.
    846847! And visibility following Kunkel, B. A., (1984): Parameterization of droplet terminal velocity and
    847 !   extinction coefficient in fog models. J. Climate Appl. Meteor., 23, 34–41.
     848!   extinction coefficient in fog models. J. Climate Appl. Meteor., 23, 34-41.
    848849
    849850    IMPLICIT NONE
     
    13571358  END SUBROUTINE compute_Koeppen_Geiger_climates
    13581359
     1360  SUBROUTINE compute_tws_RK1(d1, tas, hurs, tws)
     1361! Subroutine to compute Wet Bulb temperature of 1D series of values using equation after:
     1362!    Stull, R. (2011), J. Appl. Meteor. Climatol. 50(11):2267-2269. doi: 10.1175/JAMC-D-11-0143.1
     1363
     1364    IMPLICIT NONE
     1365
     1366    INTEGER, INTENT(in)                                  :: d1
     1367    REAL(r_k), DIMENSION(d1), INTENT(in)                 :: tas, hurs
     1368    REAL(r_k), DIMENSION(d1), INTENT(out)                :: tws
     1369 
     1370! Local
     1371    INTEGER                                              :: it
     1372
     1373!!!!!!! Variables
     1374! tas: 2-m air temperature [K]
     1375! hurs: 2-m relative humidity [1]
     1376
     1377    fname = 'compute_tws_RK1'
     1378
     1379    DO it=1, d1
     1380      tws(it) = var_tws_S11(tas(it), hurs(it))
     1381    END DO
     1382
     1383    RETURN
     1384
     1385  END SUBROUTINE compute_tws_RK1
     1386
     1387  SUBROUTINE compute_tws_RK2(d1, d2, tas, hurs, tws)
     1388! Subroutine to compute Wet Bulb temperature of 2D series of values using equation after:
     1389!    Stull, R. (2011), J. Appl. Meteor. Climatol. 50(11):2267-2269. doi: 10.1175/JAMC-D-11-0143.1
     1390
     1391    IMPLICIT NONE
     1392
     1393    INTEGER, INTENT(in)                                  :: d1, d2
     1394    REAL(r_k), DIMENSION(d1,d2), INTENT(in)              :: tas, hurs
     1395    REAL(r_k), DIMENSION(d1,d2), INTENT(out)             :: tws
     1396 
     1397! Local
     1398    INTEGER                                              :: i, j
     1399
     1400!!!!!!! Variables
     1401! tas: 2-m air temperature [K]
     1402! hurs: 2-m relative humidity [1]
     1403
     1404    fname = 'compute_tws_RK2'
     1405
     1406    DO i=1, d1
     1407      DO j=1, d2
     1408        tws(i,j) = var_tws_S11(tas(i,j), hurs(i,j))
     1409      END DO
     1410    END DO
     1411
     1412    RETURN
     1413
     1414  END SUBROUTINE compute_tws_RK2
     1415
     1416  SUBROUTINE compute_tws_RK3(d1, d2, d3, tas, hurs, tws)
     1417! Subroutine to compute Wet Bulb temperature of 3D series of values using equation after:
     1418!    Stull, R. (2011), J. Appl. Meteor. Climatol. 50(11):2267-2269. doi: 10.1175/JAMC-D-11-0143.1
     1419
     1420    IMPLICIT NONE
     1421
     1422    INTEGER, INTENT(in)                                  :: d1, d2, d3
     1423    REAL(r_k), DIMENSION(d1,d2,d3), INTENT(in)           :: tas, hurs
     1424    REAL(r_k), DIMENSION(d1,d2,d3), INTENT(out)          :: tws
     1425 
     1426! Local
     1427    INTEGER                                              :: i, j, k
     1428
     1429!!!!!!! Variables
     1430! tas: 2-m air temperature [K]
     1431! hurs: 2-m relative humidity [1]
     1432
     1433    fname = 'compute_tws_RK3'
     1434
     1435    DO i=1, d1
     1436      DO j=1, d2
     1437        DO k=1, d3
     1438          tws(i,j,k) = var_tws_S11(tas(i,j,k), hurs(i,j,k))
     1439        END DO
     1440      END DO
     1441    END DO
     1442
     1443    RETURN
     1444
     1445  END SUBROUTINE compute_tws_RK3
     1446
     1447  SUBROUTINE compute_tws_RK4(d1, d2, d3, d4, tas, hurs, tws)
     1448! Subroutine to compute Wet Bulb temperature of 4D series of values using equation after:
     1449!    Stull, R. (2011), J. Appl. Meteor. Climatol. 50(11):2267-2269. doi: 10.1175/JAMC-D-11-0143.1
     1450
     1451    IMPLICIT NONE
     1452
     1453    INTEGER, INTENT(in)                                  :: d1, d2, d3, d4
     1454    REAL(r_k), DIMENSION(d1,d2,d3,d4), INTENT(in)        :: tas, hurs
     1455    REAL(r_k), DIMENSION(d1,d2,d3,d4), INTENT(out)       :: tws
     1456 
     1457! Local
     1458    INTEGER                                              :: i,j,k,l
     1459
     1460!!!!!!! Variables
     1461! tas: 2-m air temperature [K]
     1462! hurs: 2-m relative humidity [1]
     1463
     1464    fname = 'compute_tws_RK4'
     1465
     1466    DO i=1, d1
     1467      DO j=1, d2
     1468       DO k=1, d3
     1469         DO l=1, d4
     1470           tws(i,j,k,l) = var_tws_S11(tas(i,j,k,l), hurs(i,j,k,l))
     1471         END DO
     1472        END DO
     1473      END DO
     1474    END DO
     1475
     1476    RETURN
     1477
     1478  END SUBROUTINE compute_tws_RK4
     1479
    13591480END MODULE module_ForDiagnostics
Note: See TracChangeset for help on using the changeset viewer.