Changeset 1523 for trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phytitan
- Timestamp:
- Mar 28, 2016, 5:27:51 PM (9 years ago)
- Location:
- trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phytitan
- Files:
-
- 2 edited
- 1 moved
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phytitan/iniphysiq_mod.F90
r1520 r1523 1 1 ! 2 2 ! $Id: iniphysiq.F90 2225 2015-03-11 14:55:23Z emillour $ 3 3 ! 4 MODULE iniphysiq_mod 5 6 CONTAINS 4 7 5 8 SUBROUTINE iniphysiq(iim,jjm,nlayer,punjours, pdayref,ptimestep, & 6 rlatu,rl onv,aire,cu,cv,&9 rlatu,rlatv,rlonu,rlonv,aire,cu,cv, & 7 10 prad,pg,pr,pcpp,iflag_phys) 8 11 USE dimphy, ONLY: klev ! number of atmospheric levels … … 19 22 rlond, & ! longitudes 20 23 rlatd ! latitudes 24 USE regular_lonlat_mod, ONLY : init_regular_lonlat, & 25 east, west, north, south, & 26 north_east, north_west, & 27 south_west, south_east 28 USE nrtype, ONLY: pi 21 29 IMPLICIT NONE 22 30 … … 38 46 INTEGER, INTENT (IN) :: jjm ! number of atompsheric columns along latitudes 39 47 REAL, INTENT (IN) :: rlatu(jjm+1) ! latitudes of the physics grid 48 REAL, INTENT (IN) :: rlatv(jjm) ! latitude boundaries of the physics grid 40 49 REAL, INTENT (IN) :: rlonv(iim+1) ! longitudes of the physics grid 50 REAL, INTENT (IN) :: rlonu(iim+1) ! longitude boundaries of the physics grid 41 51 REAL, INTENT (IN) :: aire(iim+1,jjm+1) ! area of the dynamics grid (m2) 42 52 REAL, INTENT (IN) :: cu((iim+1)*(jjm+1)) ! cu coeff. (u_covariant = cu * u) … … 52 62 REAL :: total_area_phy, total_area_dyn 53 63 64 ! boundaries, on global grid 65 REAL,ALLOCATABLE :: boundslon_reg(:,:) 66 REAL,ALLOCATABLE :: boundslat_reg(:,:) 54 67 55 68 ! global array, on full physics grid: … … 66 79 WRITE (lunout, *) 'klev = ', klev 67 80 abort_message = '' 68 CALL abort_gcm(modname, abort_message, 1)81 CALL abort_gcm(modname, 'Problem with dimensions', 1) 69 82 END IF 70 83 71 84 !call init_phys_lmdz(iim,jjm+1,llm,1,(/(jjm-1)*iim+2/)) 72 85 86 ! init regular global longitude-latitude grid points and boundaries 87 ALLOCATE(boundslon_reg(iim,2)) 88 ALLOCATE(boundslat_reg(jjm+1,2)) 89 90 DO i=1,iim 91 boundslon_reg(i,east)=rlonu(i) 92 boundslon_reg(i,west)=rlonu(i+1) 93 ENDDO 94 95 boundslat_reg(1,north)= PI/2 96 boundslat_reg(1,south)= rlatv(1) 97 DO j=2,jjm 98 boundslat_reg(j,north)=rlatv(j-1) 99 boundslat_reg(j,south)=rlatv(j) 100 ENDDO 101 boundslat_reg(jjm+1,north)= rlatv(jjm) 102 boundslat_reg(jjm+1,south)= -PI/2 103 104 ! Write values in module regular_lonlat_mod 105 CALL init_regular_lonlat(iim,jjm+1, rlonv(1:iim), rlatu, & 106 boundslon_reg, boundslat_reg) 107 73 108 ! Generate global arrays on full physics grid 74 109 ALLOCATE(latfi(klon_glo),lonfi(klon_glo),cufi(klon_glo),cvfi(klon_glo)) … … 194 229 195 230 END SUBROUTINE iniphysiq 231 232 END MODULE iniphysiq_mod -
trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phytitan/newstart.F
r1443 r1523 286 286 ELSE 287 287 CALL getin('ysinus',ysinus) 288 tab_cntrl(27) = ysinus 288 IF (ysinus) THEN 289 tab_cntrl(27) = 1 290 ELSE 291 tab_cntrl(27) = 0 292 ENDIF 289 293 ENDIF 290 294 -
trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phytitan/startvar.F90
r1442 r1523 363 363 SUBROUTINE start_init_orog(iml,jml,lon_in,lat_in) 364 364 USE comconst_mod 365 USE grid_atob_m, ONLY: rugsoro 365 366 366 367 !------------------------------------------------------------------------------- … … 427 428 ALLOCATE(rugo (iml ,jml)) 428 429 ALLOCATE(tmp_var(iml-1,jml)) 429 CALL rugsoro( iml_rel, jml_rel, lon_rad, lat_rad, relief_hi, iml-1, jml, &430 CALL rugsoro(lon_rad, lat_rad, relief_hi, & 430 431 lon_in, lat_in, tmp_var) 431 432 rugo(1:iml-1,:)=tmp_var; rugo(iml,:)=tmp_var(1,:) … … 727 728 728 729 USE inter_barxy_m, only: inter_barxy 730 USE grid_atob_m, only: grille_m 729 731 730 732 ! Arguments: … … 757 759 CALL inter_barxy(lon, lat(:jj-1), vari, lon2(:i1-1), lat2(:j2), vtmp) 758 760 ELSE 759 CALL grille_m ( ii, jj, lon, lat, vari, i1-1, j1, lon1, lat1,vtmp)761 CALL grille_m (lon, lat, vari, lon1, lat1, vtmp) 760 762 END IF 761 763 CALL gr_int_dyn(vtmp, varo, i1-1, j1)
Note: See TracChangeset
for help on using the changeset viewer.