Changeset 2642 in lmdz_wrf for trunk/tools/module_ForDiagnosticsVars.f90
- Timestamp:
- Jun 28, 2019, 9:40:39 PM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/tools/module_ForDiagnosticsVars.f90
r2387 r2642 34 34 ! var_fog_RUC: fog and visibility following RUC method Smirnova, (2000) 35 35 ! var_fog_FRAML50: fog and visibility following Gultepe and Milbrandt, (2010) 36 ! var_front_R04: Subroutine to compute presence of a front following Rodrigues et al.(2004) 36 37 ! var_potevap_orPM: potential evapotranspiration following Penman-Monteith formulation implemented in ORCHIDEE 37 38 ! var_psl_ecmwf: sea level pressure using ECMWF method following Mats Hamrud and Philippe Courtier [Pa] … … 1976 1977 END SUBROUTINE Svar_tws_S11 1977 1978 1979 SUBROUTINE var_front_R04(dx, dy, dt, tas, uas, vas, ddx, ddy, front) 1980 ! Subroutine to compute presence of a front following 1981 ! Rodrigues et al.(2004), Rev. Bras. Geofis. 22, 135-151, doi: 10.1590/S0102-261X2004000200004 1982 1983 IMPLICIT NONE 1984 1985 INTEGER, INTENT(in) :: dx, dy, dt 1986 REAL(r_k), DIMENSION(dx,dy), INTENT(in) :: ddx, ddy 1987 REAL(r_k), DIMENSION(dx,dy,dt), INTENT(in) :: tas, uas, vas 1988 INTEGER, DIMENSION(dx,dy,dt), INTENT(out) :: front 1989 1990 ! Local 1991 INTEGER :: i, j, l 1992 REAL, DIMENSION(dx,dy,dt) :: dt1uas, dt1vas, dt1tas, dc1wss, d2tas 1993 1994 !!!!!!! Variables 1995 ! tas: 2-m temperature [K] 1996 ! dd[x/y]: real distance between grid points along x and y axes [m] 1997 ! uas: 10m eastward wind speed [ms-1] 1998 ! vas: 10m northward wind speed [ms-1] 1999 ! front: presence of a front in the grid point [0: no, 1: yes] 2000 2001 fname = 'var_front_R04' 2002 2003 dt1uas = zeroRK 2004 dt1vas = zeroRK 2005 dt1tas = zeroRK 2006 dc1wss = zeroRK 2007 d2tas = zeroRK 2008 2009 ! 1-time-step derivatives 2010 DO l=1,dt-1 2011 dt1tas(:,:,l) = ABS(tas(:,:,l+1) - tas(:,:,l)) 2012 dt1vas(:,:,l) = ABS(vas(:,:,l+1) - vas(:,:,l)) 2013 END DO 2014 2015 ! First order curl 2016 DO l=1,dt-1 2017 CALL curl2D_1o(dx,dy,ddx,ddy,uas(:,:,l),vas(:,:,l),dc1wss(:,:,l)) 2018 END DO 2019 2020 ! 2-time-step centered derivatives 2021 DO l=2,dt-1 2022 d2tas(:,:,l) = ABS(tas(:,:,l+1) - tas(:,:,l-1)) 2023 END DO 2024 2025 front = 0 2026 DO l=1,dt 2027 DO i=1,dx 2028 DO j=1,dy 2029 IF ( (dc1wss(i,j,l) /= zeroRK) .AND. (d2tas(i,j,l) > 0.5) ) front(i,j,l) = 1 2030 END DO 2031 END DO 2032 END DO 2033 2034 RETURN 2035 2036 END SUBROUTINE var_front_R04 2037 1978 2038 END MODULE module_ForDiagnosticsVars
Note: See TracChangeset
for help on using the changeset viewer.