MODULE mo_convect_tables !----------------------------------------------------------------------- ! *mo_convect_tables* - tables for convective adjustment code 5: ! ! d.salmond cray (uk) 12/8/91 ! ! ! table lookups replaced 10: ! ! A. Rhodin mpi 12/98 ! ! When replacing the table lookups the following code has been used: ! 15: ! tlucua : c2es*EXP(MERGE(c3les,c3ies,lo)*(tt-tmelt) & ! / (tt-MERGE(c4les,c4ies,lo))) ! ! tlucub : MERGE(c5alvcp,c5alscp,lo) / (tt-MERGE(c4les,c4ies,lo))**2 ! 20: ! tlucuc : MERGE(alvdcp, alsdcp, lo) ! ! tlucuaw: c2es*EXP(c3les*(tt-tmelt)*(1./(tt-c4les))) ! ! with: lo = tt > tmelt 25: ! ! compile with option -DNOLOOKUP in order to replace lookup tables !----------------------------------------------------------------------- IMPLICIT NONE 30: SAVE !---------------- ! Public entities !---------------- 35: PRIVATE !----------------------------- ! lookup tables -- obsolescent !----------------------------- PUBLIC :: jptlucu1 ! lookup table lower bound 40: PUBLIC :: jptlucu2 ! lookup table upper bound PUBLIC :: tlucua ! table -- e_s*Rd/Rv PUBLIC :: tlucub ! table -- for derivative calculation: d es/ d t PUBLIC :: tlucuc ! table -- l/cp PUBLIC :: tlucuaw ! table 45: PUBLIC :: set_lookup_tables ! initialization routine !----------------- ! Module variables !----------------- 50: INTEGER, PARAMETER :: jptlucu1 = 50000 ! lookup table lower bound INTEGER, PARAMETER :: jptlucu2 = 370000 ! lookup table upper bound REAL :: tlucua(jptlucu1:jptlucu2) ! table - e_s*Rd/Rv REAL :: tlucub(jptlucu1:jptlucu2) ! table - for derivative calculation 55: REAL :: tlucuc(jptlucu1:jptlucu2) ! table - l/cp REAL :: tlucuaw(jptlucu1:jptlucu2) ! table CONTAINS 60: SUBROUTINE set_lookup_tables !---------------------------- ! -- Initialise lookup tables ! called from 'setphys' !---------------------------- 65: USE mo_constants, ONLY: alsdcp, alvdcp, c2es, c3ies, c3les, c4ies, c4les, & c5alscp, c5alvcp, tmelt REAL :: tt INTEGER :: it LOGICAL :: lo 70: tt = jptlucu1 * 0.001 DO it = jptlucu1, jptlucu2 lo = tt>tmelt tlucua(it) = c2es*EXP(MERGE(c3les, c3ies, lo)*(tt-tmelt) & 75: * (1./(tt-MERGE(c4les, c4ies, lo)))) tlucub(it) = MERGE(c5alvcp,c5alscp,lo) & * (1./(tt-MERGE(c4les, c4ies, lo)))**2 tlucuc(it) = MERGE(alvdcp, alsdcp, lo) 80: tlucuaw(it)= c2es*EXP(c3les*(tt-tmelt)*(1./(tt-c4les))) tt = tt + 0.001 END DO END SUBROUTINE set_lookup_tables 85: END MODULE mo_convect_tablesback to top
Info Section uses: mo_constants
HTML derived from FORTRAN source by f2html.pl v0.3 (C) 1997,98 Beroud Jean-Marc.