Changeset 3819
- Timestamp:
- Apr 22, 2015, 6:28:50 PM (10 years ago)
- Location:
- dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd
- Files:
-
- 26 edited
Legend:
- Unmodified
- Added
- Removed
-
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cfmip_point_locations.F90
r3809 r3819 34 34 USE dimphy 35 35 USE iophy 36 USE mod_grid_phy_lmdz 36 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, klon_glo 37 37 38 38 IMPLICIT none 39 #include "dimensions.h"40 39 INTEGER :: npCFMIP 41 40 REAL, DIMENSION(npCFMIP) :: lonCFMIP, latCFMIP … … 44 43 REAL :: dlon1, dlon2 45 44 REAL :: dlat1, dlat2 46 REAL, DIMENSION( iim+1) :: lon45 REAL, DIMENSION(nbp_lon+1) :: lon 47 46 INTEGER, DIMENSION(npCFMIP) :: tabijGCM 48 47 REAL, DIMENSION(npCFMIP) :: lonGCM, latGCM 49 48 50 lon(1: iim)=io_lon(:)51 lon( iim+1)=-1*lon(1)49 lon(1:nbp_lon)=io_lon(:) 50 lon(nbp_lon+1)=-1*lon(1) 52 51 OPEN(22, file="LMDZ_pointsCFMIP.txt") 53 52 DO np=1, npCFMIP 54 DO i=1, iim53 DO i=1, nbp_lon 55 54 ! 56 55 ! PRINT*,'IM np i lonCF lonGCM lonGCM+1',np,i,lonCFMIP(np),lon(i), & … … 85 84 ELSE 86 85 j=j+1 87 IF(j.LE. jjm) THEN86 IF(j.LE.nbp_lat-1) THEN 88 87 GOTO 40 89 88 ENDIF … … 99 98 lonGCM(ip)=lon(ipt(ip)) 100 99 latGCM(ip)=io_lat(jpt(ip)) 101 if(jpt(ip).GE.2.AND.jpt(ip).LE. jjm) THEN102 tabijGCM(ip)=1+(jpt(ip)-2)* iim+ipt(ip)100 if(jpt(ip).GE.2.AND.jpt(ip).LE. nbp_lat-1) THEN 101 tabijGCM(ip)=1+(jpt(ip)-2)*nbp_lon+ipt(ip) 103 102 else if(jpt(ip).EQ.1) THEN 104 103 tabijGCM(ip)=1 105 else if(jpt(ip).EQ. jjm+1) THEN104 else if(jpt(ip).EQ.nbp_lat) THEN 106 105 tabijGCM(ip)=klon_glo 107 106 else -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/cpl_mod.F90
r3817 r3819 103 103 USE surface_data 104 104 USE indice_sol_mod 105 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, grid1dTo2d_glo 105 106 ! USE temps_phy_mod 106 107 USE inifis_mod, ONLY: annee_ref, day_ini, itau_phy, itaufin, lunout 107 INCLUDE "dimensions.h"108 108 109 109 ! Input arguments … … 121 121 INTEGER :: npas ! only for OASIS2 122 122 REAL :: zjulian 123 REAL, DIMENSION( iim,jjm+1) :: zx_lon, zx_lat123 REAL, DIMENSION(nbp_lon,nbp_lat) :: zx_lon, zx_lat 124 124 CHARACTER(len = 20) :: modname = 'cpl_init' 125 125 CHARACTER(len = 80) :: abort_message … … 172 172 ALLOCATE(cpl_taumod(klon,2), stat = error) 173 173 sum_error = sum_error + error 174 ALLOCATE(cpl_rriv2D( iim,jj_nb), stat=error)175 sum_error = sum_error + error 176 ALLOCATE(cpl_rcoa2D( iim,jj_nb), stat=error)177 sum_error = sum_error + error 178 ALLOCATE(cpl_rlic2D( iim,jj_nb), stat=error)179 sum_error = sum_error + error 180 ALLOCATE(read_sst( iim, jj_nb), stat = error)181 sum_error = sum_error + error 182 ALLOCATE(read_sic( iim, jj_nb), stat = error)183 sum_error = sum_error + error 184 ALLOCATE(read_sit( iim, jj_nb), stat = error)185 sum_error = sum_error + error 186 ALLOCATE(read_alb_sic( iim, jj_nb), stat = error)187 sum_error = sum_error + error 188 ALLOCATE(read_u0( iim, jj_nb), stat = error)189 sum_error = sum_error + error 190 ALLOCATE(read_v0( iim, jj_nb), stat = error)174 ALLOCATE(cpl_rriv2D(nbp_lon,jj_nb), stat=error) 175 sum_error = sum_error + error 176 ALLOCATE(cpl_rcoa2D(nbp_lon,jj_nb), stat=error) 177 sum_error = sum_error + error 178 ALLOCATE(cpl_rlic2D(nbp_lon,jj_nb), stat=error) 179 sum_error = sum_error + error 180 ALLOCATE(read_sst(nbp_lon, jj_nb), stat = error) 181 sum_error = sum_error + error 182 ALLOCATE(read_sic(nbp_lon, jj_nb), stat = error) 183 sum_error = sum_error + error 184 ALLOCATE(read_sit(nbp_lon, jj_nb), stat = error) 185 sum_error = sum_error + error 186 ALLOCATE(read_alb_sic(nbp_lon, jj_nb), stat = error) 187 sum_error = sum_error + error 188 ALLOCATE(read_u0(nbp_lon, jj_nb), stat = error) 189 sum_error = sum_error + error 190 ALLOCATE(read_v0(nbp_lon, jj_nb), stat = error) 191 191 sum_error = sum_error + error 192 192 193 193 IF (carbon_cycle_cpl) THEN 194 ALLOCATE(read_co2( iim, jj_nb), stat = error)194 ALLOCATE(read_co2(nbp_lon, jj_nb), stat = error) 195 195 sum_error = sum_error + error 196 196 ALLOCATE(cpl_atm_co2(klon,2), stat = error) … … 230 230 idayref = day_ini 231 231 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) 232 CALL gr _fi_ecrit(1,klon,iim,jjm+1,rlon,zx_lon)233 DO i = 1, iim232 CALL grid1dTo2d_glo(rlon,zx_lon) 233 DO i = 1, nbp_lon 234 234 zx_lon(i,1) = rlon(i+1) 235 zx_lon(i, jjm+1) = rlon(i+1)235 zx_lon(i,nbp_lat) = rlon(i+1) 236 236 ENDDO 237 CALL gr _fi_ecrit(1,klon,iim,jjm+1,rlat,zx_lat)237 CALL grid1dTo2d_glo(rlat,zx_lat) 238 238 clintocplnam="cpl_atm_tauflx" 239 CALL histbeg(clintocplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),&240 1, iim,1,jjm+1, itau_phy,zjulian,dtime,nhoridct,nidct)239 CALL histbeg(clintocplnam, nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),& 240 1,nbp_lon,1,nbp_lat, itau_phy,zjulian,dtime,nhoridct,nidct) 241 241 ! no vertical axis 242 242 CALL histdef(nidct, 'tauxe','tauxe', & 243 "-", iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)243 "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime) 244 244 CALL histdef(nidct, 'tauyn','tauyn', & 245 "-", iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)245 "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime) 246 246 CALL histdef(nidct, 'tmp_lon','tmp_lon', & 247 "-", iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)247 "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime) 248 248 CALL histdef(nidct, 'tmp_lat','tmp_lat', & 249 "-", iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)249 "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime) 250 250 DO jf=1,maxsend 251 251 IF (infosend(i)%action) THEN 252 252 CALL histdef(nidct, infosend(i)%name ,infosend(i)%name , & 253 "-", iim, jjm+1, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime)253 "-",nbp_lon, nbp_lat, nhoridct, 1, 1, 1, -99, 32, "inst", dtime,dtime) 254 254 ENDIF 255 255 END DO … … 258 258 259 259 clfromcplnam="cpl_atm_sst" 260 CALL histbeg(clfromcplnam, iim,zx_lon(:,1),jjm+1,zx_lat(1,:),1,iim,1,jjm+1, &260 CALL histbeg(clfromcplnam, nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:),1,nbp_lon,1,nbp_lat, & 261 261 0,zjulian,dtime,nhoridcs,nidcs) 262 262 ! no vertical axis … … 264 264 IF (inforecv(i)%action) THEN 265 265 CALL histdef(nidcs,inforecv(i)%name ,inforecv(i)%name , & 266 "-", iim, jjm+1, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime)266 "-",nbp_lon, nbp_lat, nhoridcs, 1, 1, 1, -99, 32, "inst", dtime,dtime) 267 267 ENDIF 268 268 END DO … … 299 299 ! USE temps_phy_mod 300 300 USE inifis_mod, ONLY: start_time, itau_phy 301 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 301 302 302 303 INCLUDE "YOMCST.h" 303 INCLUDE "dimensions.h"304 305 304 ! Arguments 306 305 !************************************************************************************ … … 314 313 INTEGER :: j, i, time_sec 315 314 INTEGER :: itau_w 316 INTEGER, DIMENSION( iim*(jjm+1)):: ndexcs315 INTEGER, DIMENSION(nbp_lon*nbp_lat) :: ndexcs 317 316 CHARACTER(len = 20) :: modname = 'cpl_receive_frac' 318 317 CHARACTER(len = 80) :: abort_message 319 318 REAL, DIMENSION(klon) :: read_sic1D 320 REAL, DIMENSION( iim,jj_nb,maxrecv):: tab_read_flds319 REAL, DIMENSION(nbp_lon,jj_nb,maxrecv) :: tab_read_flds 321 320 REAL, DIMENSION(klon,nbsrf) :: pctsrf_old 322 321 REAL, DIMENSION(klon_mpi) :: rlon_mpi, rlat_mpi 323 REAL, DIMENSION( iim, jj_nb):: tmp_lon, tmp_lat324 REAL, DIMENSION( iim, jj_nb):: tmp_r0322 REAL, DIMENSION(nbp_lon, jj_nb) :: tmp_lon, tmp_lat 323 REAL, DIMENSION(nbp_lon, jj_nb) :: tmp_r0 325 324 326 325 !************************************************************************************* … … 349 348 DO i = 1, maxrecv 350 349 IF (inforecv(i)%action) THEN 351 CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i), iim*(jjm+1),ndexcs)350 CALL histwrite(nidcs,inforecv(i)%name,itau_w,tab_read_flds(:,:,i),nbp_lon*nbp_lat,ndexcs) 352 351 ENDIF 353 352 END DO … … 374 373 ! Transform the currents from cartesian to spheric coordinates 375 374 ! tmp_r0 should be zero 376 CALL geo2atm( iim, jj_nb, tab_read_flds(:,:,idr_curenx), &375 CALL geo2atm(nbp_lon, jj_nb, tab_read_flds(:,:,idr_curenx), & 377 376 tab_read_flds(:,:,idr_cureny), tab_read_flds(:,:,idr_curenz), & 378 377 tmp_lon, tmp_lat, & … … 543 542 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl, co2_send 544 543 USE indice_sol_mod 545 INCLUDE "dimensions.h"544 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 546 545 547 546 ! Input arguments … … 636 635 IF (.NOT. ALLOCATED(cpl_sols2D)) THEN 637 636 sum_error = 0 638 ALLOCATE(cpl_sols2D( iim,jj_nb,2), stat=error)639 sum_error = sum_error + error 640 ALLOCATE(cpl_nsol2D( iim,jj_nb,2), stat=error)641 sum_error = sum_error + error 642 ALLOCATE(cpl_rain2D( iim,jj_nb,2), stat=error)643 sum_error = sum_error + error 644 ALLOCATE(cpl_snow2D( iim,jj_nb,2), stat=error)645 sum_error = sum_error + error 646 ALLOCATE(cpl_evap2D( iim,jj_nb,2), stat=error)647 sum_error = sum_error + error 648 ALLOCATE(cpl_tsol2D( iim,jj_nb,2), stat=error)649 sum_error = sum_error + error 650 ALLOCATE(cpl_fder2D( iim,jj_nb,2), stat=error)651 sum_error = sum_error + error 652 ALLOCATE(cpl_albe2D( iim,jj_nb,2), stat=error)653 sum_error = sum_error + error 654 ALLOCATE(cpl_taux2D( iim,jj_nb,2), stat=error)655 sum_error = sum_error + error 656 ALLOCATE(cpl_tauy2D( iim,jj_nb,2), stat=error)657 sum_error = sum_error + error 658 ALLOCATE(cpl_windsp2D( iim,jj_nb), stat=error)659 sum_error = sum_error + error 660 ALLOCATE(cpl_taumod2D( iim,jj_nb,2), stat=error)637 ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error) 638 sum_error = sum_error + error 639 ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error) 640 sum_error = sum_error + error 641 ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error) 642 sum_error = sum_error + error 643 ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error) 644 sum_error = sum_error + error 645 ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error) 646 sum_error = sum_error + error 647 ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error) 648 sum_error = sum_error + error 649 ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error) 650 sum_error = sum_error + error 651 ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error) 652 sum_error = sum_error + error 653 ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error) 654 sum_error = sum_error + error 655 ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error) 656 sum_error = sum_error + error 657 ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error) 658 sum_error = sum_error + error 659 ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error) 661 660 sum_error = sum_error + error 662 661 663 662 IF (carbon_cycle_cpl) THEN 664 ALLOCATE(cpl_atm_co22D( iim,jj_nb), stat=error)663 ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error) 665 664 sum_error = sum_error + error 666 665 END IF … … 734 733 USE carbon_cycle_mod, ONLY : carbon_cycle_cpl 735 734 USE indice_sol_mod 736 INCLUDE "dimensions.h"735 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 737 736 738 737 ! Input arguments … … 821 820 IF (.NOT. ALLOCATED(cpl_sols2D)) THEN 822 821 sum_error = 0 823 ALLOCATE(cpl_sols2D( iim,jj_nb,2), stat=error)824 sum_error = sum_error + error 825 ALLOCATE(cpl_nsol2D( iim,jj_nb,2), stat=error)826 sum_error = sum_error + error 827 ALLOCATE(cpl_rain2D( iim,jj_nb,2), stat=error)828 sum_error = sum_error + error 829 ALLOCATE(cpl_snow2D( iim,jj_nb,2), stat=error)830 sum_error = sum_error + error 831 ALLOCATE(cpl_evap2D( iim,jj_nb,2), stat=error)832 sum_error = sum_error + error 833 ALLOCATE(cpl_tsol2D( iim,jj_nb,2), stat=error)834 sum_error = sum_error + error 835 ALLOCATE(cpl_fder2D( iim,jj_nb,2), stat=error)836 sum_error = sum_error + error 837 ALLOCATE(cpl_albe2D( iim,jj_nb,2), stat=error)838 sum_error = sum_error + error 839 ALLOCATE(cpl_taux2D( iim,jj_nb,2), stat=error)840 sum_error = sum_error + error 841 ALLOCATE(cpl_tauy2D( iim,jj_nb,2), stat=error)842 sum_error = sum_error + error 843 ALLOCATE(cpl_windsp2D( iim,jj_nb), stat=error)844 sum_error = sum_error + error 845 ALLOCATE(cpl_taumod2D( iim,jj_nb,2), stat=error)822 ALLOCATE(cpl_sols2D(nbp_lon,jj_nb,2), stat=error) 823 sum_error = sum_error + error 824 ALLOCATE(cpl_nsol2D(nbp_lon,jj_nb,2), stat=error) 825 sum_error = sum_error + error 826 ALLOCATE(cpl_rain2D(nbp_lon,jj_nb,2), stat=error) 827 sum_error = sum_error + error 828 ALLOCATE(cpl_snow2D(nbp_lon,jj_nb,2), stat=error) 829 sum_error = sum_error + error 830 ALLOCATE(cpl_evap2D(nbp_lon,jj_nb,2), stat=error) 831 sum_error = sum_error + error 832 ALLOCATE(cpl_tsol2D(nbp_lon,jj_nb,2), stat=error) 833 sum_error = sum_error + error 834 ALLOCATE(cpl_fder2D(nbp_lon,jj_nb,2), stat=error) 835 sum_error = sum_error + error 836 ALLOCATE(cpl_albe2D(nbp_lon,jj_nb,2), stat=error) 837 sum_error = sum_error + error 838 ALLOCATE(cpl_taux2D(nbp_lon,jj_nb,2), stat=error) 839 sum_error = sum_error + error 840 ALLOCATE(cpl_tauy2D(nbp_lon,jj_nb,2), stat=error) 841 sum_error = sum_error + error 842 ALLOCATE(cpl_windsp2D(nbp_lon,jj_nb), stat=error) 843 sum_error = sum_error + error 844 ALLOCATE(cpl_taumod2D(nbp_lon,jj_nb,2), stat=error) 846 845 sum_error = sum_error + error 847 846 848 847 IF (carbon_cycle_cpl) THEN 849 ALLOCATE(cpl_atm_co22D( iim,jj_nb), stat=error)848 ALLOCATE(cpl_atm_co22D(nbp_lon,jj_nb), stat=error) 850 849 sum_error = sum_error + error 851 850 END IF … … 914 913 ! (it is done in cpl_send_seaice_fields). 915 914 ! 916 INCLUDE "dimensions.h"915 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 917 916 918 917 ! Input arguments … … 926 925 ! Local variables 927 926 !************************************************************************************* 928 REAL, DIMENSION( iim,jj_nb) :: rriv2D929 REAL, DIMENSION( iim,jj_nb) :: rcoa2D927 REAL, DIMENSION(nbp_lon,jj_nb) :: rriv2D 928 REAL, DIMENSION(nbp_lon,jj_nb) :: rcoa2D 930 929 931 930 !************************************************************************************* … … 968 967 969 968 SUBROUTINE cpl_send_landice_fields(itime, knon, knindex, rlic_in) 969 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 970 970 ! This subroutine cumulates the field for melting ice for each time-step 971 971 ! during a coupling period. This routine will not send to coupler. Sending 972 972 ! will be done in cpl_send_seaice_fields. 973 973 ! 974 975 INCLUDE "dimensions.h"976 974 977 975 ! Input varibales … … 984 982 ! Local varibales 985 983 !************************************************************************************* 986 REAL, DIMENSION( iim,jj_nb) :: rlic2D984 REAL, DIMENSION(nbp_lon,jj_nb) :: rlic2D 987 985 988 986 !************************************************************************************* … … 1033 1031 ! Some includes 1034 1032 !************************************************************************************* 1035 INCLUDE "dimensions.h"1033 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 1036 1034 1037 1035 ! Input arguments … … 1048 1046 INTEGER :: itau_w 1049 1047 INTEGER :: time_sec 1050 INTEGER, DIMENSION( iim*(jjm+1)):: ndexct1048 INTEGER, DIMENSION(nbp_lon*nbp_lat) :: ndexct 1051 1049 REAL :: Up, Down 1052 REAL, DIMENSION( iim, jj_nb):: tmp_lon, tmp_lat1053 REAL, DIMENSION( iim, jj_nb, 4):: pctsrf2D1054 REAL, DIMENSION( iim, jj_nb):: deno1050 REAL, DIMENSION(nbp_lon, jj_nb) :: tmp_lon, tmp_lat 1051 REAL, DIMENSION(nbp_lon, jj_nb, 4) :: pctsrf2D 1052 REAL, DIMENSION(nbp_lon, jj_nb) :: deno 1055 1053 CHARACTER(len = 20) :: modname = 'cpl_send_all' 1056 1054 CHARACTER(len = 80) :: abort_message 1057 1055 1058 1056 ! Variables with fields to coupler 1059 REAL, DIMENSION( iim, jj_nb):: tmp_taux1060 REAL, DIMENSION( iim, jj_nb):: tmp_tauy1061 REAL, DIMENSION( iim, jj_nb):: tmp_calv1057 REAL, DIMENSION(nbp_lon, jj_nb) :: tmp_taux 1058 REAL, DIMENSION(nbp_lon, jj_nb) :: tmp_tauy 1059 REAL, DIMENSION(nbp_lon, jj_nb) :: tmp_calv 1062 1060 ! Table with all fields to send to coupler 1063 REAL, DIMENSION( iim, jj_nb, maxsend):: tab_flds1061 REAL, DIMENSION(nbp_lon, jj_nb, maxsend) :: tab_flds 1064 1062 REAL, DIMENSION(klon_mpi) :: rlon_mpi, rlat_mpi 1065 1063 … … 1115 1113 1116 1114 DO j = 1, jj_nb 1117 tmp_calv(:,j) = DOT_PRODUCT (cpl_rlic2D(1: iim,j), &1118 pctsrf2D(1: iim,j,is_lic)) / REAL(iim)1115 tmp_calv(:,j) = DOT_PRODUCT (cpl_rlic2D(1:nbp_lon,j), & 1116 pctsrf2D(1:nbp_lon,j,is_lic)) / REAL(nbp_lon) 1119 1117 ENDDO 1120 1118 … … 1136 1134 1137 1135 IF (.NOT. is_north_pole .AND. ii_begin /=1) THEN 1138 Up=Up+tmp_calv( iim,1)1136 Up=Up+tmp_calv(nbp_lon,1) 1139 1137 tmp_calv(:,1)=Up 1140 1138 ENDIF 1141 1139 1142 IF (.NOT. is_south_pole .AND. ii_end /= iim) THEN1140 IF (.NOT. is_south_pole .AND. ii_end /= nbp_lon) THEN 1143 1141 Down=Down+tmp_calv(1,jj_nb) 1144 1142 tmp_calv(:,jj_nb)=Down … … 1229 1227 IF (is_sequential) THEN 1230 1228 IF (is_north_pole) tmp_lon(:,1) = tmp_lon(:,2) 1231 IF (is_south_pole) tmp_lon(:, jjm+1) = tmp_lon(:,jjm)1229 IF (is_south_pole) tmp_lon(:,nbp_lat) = tmp_lon(:,nbp_lat-1) 1232 1230 ENDIF 1233 1231 … … 1236 1234 ndexct(:) = 0 1237 1235 itau_w = itau_phy + itime + start_time * day_step / iphysiq 1238 CALL histwrite(nidct,'tauxe',itau_w,tmp_taux, iim*(jjm+1),ndexct)1239 CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy, iim*(jjm+1),ndexct)1240 CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon, iim*(jjm+1),ndexct)1241 CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat, iim*(jjm+1),ndexct)1236 CALL histwrite(nidct,'tauxe',itau_w,tmp_taux,nbp_lon*nbp_lat,ndexct) 1237 CALL histwrite(nidct,'tauyn',itau_w,tmp_tauy,nbp_lon*nbp_lat,ndexct) 1238 CALL histwrite(nidct,'tmp_lon',itau_w,tmp_lon,nbp_lon*nbp_lat,ndexct) 1239 CALL histwrite(nidct,'tmp_lat',itau_w,tmp_lat,nbp_lon*nbp_lat,ndexct) 1242 1240 ENDIF 1243 1241 … … 1245 1243 ! cartesian 3D coordinates 1246 1244 !$OMP MASTER 1247 CALL atm2geo ( iim, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, &1245 CALL atm2geo (nbp_lon, jj_nb, tmp_taux, tmp_tauy, tmp_lon, tmp_lat, & 1248 1246 tab_flds(:,:,ids_tauxxu), tab_flds(:,:,ids_tauyyu), tab_flds(:,:,ids_tauzzu) ) 1249 1247 … … 1260 1258 DO j=1,maxsend 1261 1259 IF (infosend(j)%action) CALL histwrite(nidct,infosend(j)%name, itau_w, & 1262 tab_flds(:,:,j), iim*(jjm+1),ndexct)1260 tab_flds(:,:,j),nbp_lon*nbp_lat,ndexct) 1263 1261 ENDDO 1264 1262 ENDIF … … 1302 1300 SUBROUTINE cpl2gath(champ_in, champ_out, knon, knindex) 1303 1301 USE mod_phys_lmdz_para 1302 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 1304 1303 ! Cette routine transforme un champs de la grille 2D recu du coupleur sur la grille 1305 1304 ! 'gathered' (la grille physiq comprime). … … 1314 1313 ! champ_out champ sur la grille 'gatherd' 1315 1314 ! 1316 INCLUDE "dimensions.h"1317 1315 1318 1316 ! Input 1319 INTEGER, INTENT(IN) :: knon1320 REAL, DIMENSION( iim,jj_nb), INTENT(IN):: champ_in1321 INTEGER, DIMENSION(klon), INTENT(IN) :: knindex1317 INTEGER, INTENT(IN) :: knon 1318 REAL, DIMENSION(nbp_lon,jj_nb), INTENT(IN) :: champ_in 1319 INTEGER, DIMENSION(klon), INTENT(IN) :: knindex 1322 1320 1323 1321 ! Output … … 1333 1331 1334 1332 1335 ! Transform from 2 dimensions ( iim,jj_nb) to 1 dimension (klon)1333 ! Transform from 2 dimensions (nbp_lon,jj_nb) to 1 dimension (klon) 1336 1334 !$OMP MASTER 1337 1335 CALL Grid2Dto1D_mpi(champ_in,temp_mpi) … … 1352 1350 SUBROUTINE gath2cpl(champ_in, champ_out, knon, knindex) 1353 1351 USE mod_phys_lmdz_para 1352 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 1354 1353 ! Cette routine ecrit un champ 'gathered' sur la grille 2D pour le passer 1355 1354 ! au coupleur. … … 1363 1362 ! champ_out champ sur la grille 2D 1364 1363 ! 1365 INCLUDE "dimensions.h"1366 1364 1367 1365 ! Input arguments … … 1373 1371 ! Output arguments 1374 1372 !************************************************************************************* 1375 REAL, DIMENSION( iim,jj_nb), INTENT(OUT) :: champ_out1373 REAL, DIMENSION(nbp_lon,jj_nb), INTENT(OUT) :: champ_out 1376 1374 1377 1375 ! Local variables … … 1389 1387 ENDDO 1390 1388 1391 ! Transform from 1 dimension (klon) to 2 dimensions ( iim,jj_nb)1389 ! Transform from 1 dimension (klon) to 2 dimensions (nbp_lon,jj_nb) 1392 1390 CALL gather_omp(temp_omp,temp_mpi) 1393 1391 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_bilKP_ave.h
r3809 r3819 11 11 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) 12 12 c 13 cym CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon,zx_lon)14 cym DO i = 1, iim15 cym zx_lon(i,1) = rlon(i+1)16 cym zx_lon(i,jjmp1) = rlon(i+1)17 cym ENDDO18 13 DO ll=1,klev 19 14 znivsig(ll)=REAL(ll) 20 15 ENDDO 21 cym CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)22 cym write(*,*)'zx_lon = ',zx_lon(:,1)23 cym write(*,*)'zx_lat = ',zx_lat(1,:)24 cym CALL histbeg("histbilKP_ave", iim,zx_lon(:,1), jjmp1,25 cym . zx_lat(1,:),26 cym . 1,iim,1,jjmp1, itau_phy, zjulian, dtime,27 cym . nhori, nid_bilKPave)28 16 CALL histbeg_phy("histbilKP_ave", itau_phy, zjulian, dtime, 29 17 . nhori, nid_bilKPave) -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_bilKP_ins.h
r3809 r3819 11 11 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) 12 12 c 13 cym CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlon,zx_lon)14 cym DO i = 1, iim15 cym zx_lon(i,1) = rlon(i+1)16 cym zx_lon(i,jjmp1) = rlon(i+1)17 cym ENDDO18 13 DO ll=1,klev 19 14 znivsig(ll)=REAL(ll) 20 15 ENDDO 21 cym CALL gr_fi_ecrit(1,klon,iim,jjmp1,rlat,zx_lat)22 cym write(*,*)'zx_lon = ',zx_lon(:,1)23 cym write(*,*)'zx_lat = ',zx_lat(1,:)24 16 c 25 17 cIM 280405 BEG -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_histday_seri.h
r3818 r3819 13 13 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) 14 14 ! 15 CALL gr _fi_ecrit(1,klon,nbp_lon,jjmp1,rlon,zx_lon)15 CALL grid1dTo2d_glo(rlon,zx_lon) 16 16 DO i = 1, nbp_lon 17 17 zx_lon(i,1) = rlon(i+1) … … 21 21 znivsig(ll)=REAL(ll) 22 22 ENDDO 23 CALL gr _fi_ecrit(1,klon,nbp_lon,jjmp1,rlat,zx_lat)23 CALL grid1dTo2d_glo(rlat,zx_lat) 24 24 ! 25 25 imin_debut=1 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ini_paramLMDZ_phy.h
r3818 r3819 15 15 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) 16 16 ! 17 CALL gr _fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon_glo,zx_lon)17 CALL grid1dTo2d_glo(rlon_glo,zx_lon) 18 18 if (nbp_lon.gt.1) then 19 19 DO i = 1, nbp_lon … … 22 22 ENDDO 23 23 endif 24 CALL gr _fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat_glo,zx_lat)24 CALL grid1dTo2d_glo(rlat_glo,zx_lat) 25 25 ! 26 26 CALL histbeg("paramLMDZ_phy.nc", & -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/iophy.F90
r3817 r3819 53 53 #endif 54 54 IMPLICIT NONE 55 INCLUDE 'dimensions.h'56 55 REAL,DIMENSION(klon),INTENT(IN) :: rlon 57 56 REAL,DIMENSION(klon),INTENT(IN) :: rlat … … 76 75 77 76 !$OMP MASTER 78 ALLOCATE(io_lat( jjm+1-1/(iim*jjm)))77 ALLOCATE(io_lat(nbp_lat)) 79 78 io_lat(1)=rlat_glo(1) 80 io_lat( jjm+1-1/(iim*jjm))=rlat_glo(klon_glo)81 IF (( iim*jjm) > 1) then82 DO i=2, jjm83 io_lat(i)=rlat_glo(2+(i-2)* iim)79 io_lat(nbp_lat)=rlat_glo(klon_glo) 80 IF ((nbp_lon*nbp_lat) > 1) then 81 DO i=2,nbp_lat-1 82 io_lat(i)=rlat_glo(2+(i-2)*nbp_lon) 84 83 ENDDO 85 84 ENDIF 86 85 87 ALLOCATE(io_lon(iim)) 88 io_lon(:)=rlon_glo(2-1/(iim*jjm):iim+1-1/(iim*jjm)) 86 ALLOCATE(io_lon(nbp_lon)) 87 io_lon(1)=rlon_glo(1) 88 IF (nbp_lon > 1) io_lon(2:nbp_lon)=rlon_glo(3:nbp_lon+1) 89 89 90 !! (I) dtnb : total number of domains 90 91 !! (I) dnb : domain number … … 103 104 104 105 ddid=(/ 1,2 /) 105 dsg=(/ iim, jjm+1-1/(iim*jjm)/)106 dsl=(/ iim, jj_nb /)106 dsg=(/ nbp_lon, nbp_lat /) 107 dsl=(/ nbp_lon, jj_nb /) 107 108 dpf=(/ 1,jj_begin /) 108 dpl=(/ iim, jj_end /)109 dpl=(/ nbp_lon, jj_end /) 109 110 dhs=(/ ii_begin-1,0 /) 110 111 IF (mpi_rank==mpi_size-1) THEN 111 112 dhe=(/0,0/) 112 113 ELSE 113 dhe=(/ iim-ii_end,0 /)114 dhe=(/ nbp_lon-ii_end,0 /) 114 115 ENDIF 115 116 … … 154 155 mpi_size, mpi_rank 155 156 USE ioipsl, only: flio_dom_set 157 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 156 158 IMPLICIT NONE 157 INCLUDE 'dimensions.h' 158 REAL,DIMENSION(iim),INTENT(IN) :: lon 159 REAL,DIMENSION(jjm+1-1/(iim*jjm)),INTENT(IN) :: lat 159 REAL,DIMENSION(nbp_lon),INTENT(IN) :: lon 160 REAL,DIMENSION(nbp_lat),INTENT(IN) :: lat 160 161 161 162 INTEGER,DIMENSION(2) :: ddid … … 168 169 169 170 !$OMP MASTER 170 allocate(io_lat( jjm+1-1/(iim*jjm)))171 allocate(io_lat(nbp_lat)) 171 172 io_lat(:)=lat(:) 172 allocate(io_lon( iim))173 allocate(io_lon(nbp_lon)) 173 174 io_lon(:)=lon(:) 174 175 175 176 ddid=(/ 1,2 /) 176 dsg=(/ iim, jjm+1-1/(iim*jjm)/)177 dsl=(/ iim, jj_nb /)177 dsg=(/ nbp_lon, nbp_lat /) 178 dsl=(/ nbp_lon, jj_nb /) 178 179 dpf=(/ 1,jj_begin /) 179 dpl=(/ iim, jj_end /)180 dpl=(/ nbp_lon, jj_end /) 180 181 dhs=(/ ii_begin-1,0 /) 181 182 if (mpi_rank==mpi_size-1) then 182 183 dhe=(/0,0/) 183 184 else 184 dhe=(/ iim-ii_end,0 /)185 dhe=(/ nbp_lon-ii_end,0 /) 185 186 endif 186 187 … … 197 198 USE mod_phys_lmdz_para, only: is_sequential, is_using_mpi, is_mpi_root, & 198 199 jj_begin, jj_end, jj_nb 200 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 199 201 use ioipsl, only: histbeg 200 202 #ifdef CPP_XIOS … … 202 204 #endif 203 205 IMPLICIT NONE 204 include 'dimensions.h'205 206 include 'clesphys.h' 206 207 … … 216 217 !$OMP MASTER 217 218 if (is_sequential) then 218 call histbeg(name, iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &219 1, iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)219 call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), & 220 1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day) 220 221 else 221 call histbeg(name, iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &222 1, iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)222 call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), & 223 1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id) 223 224 endif 224 225 … … 239 240 240 241 USE mod_phys_lmdz_para, only: jj_begin, jj_end, jj_nb, is_sequential 242 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 241 243 use ioipsl, only: histbeg 242 244 243 245 IMPLICIT NONE 244 include 'dimensions.h'245 246 246 247 character*(*), INTENT(IN) :: name … … 254 255 #ifndef CPP_IOIPSL_NO_OUTPUT 255 256 if (is_sequential) then 256 call histbeg(name, iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &257 1, iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day)257 call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), & 258 1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day) 258 259 else 259 call histbeg(name, iim,io_lon, jj_nb,io_lat(jj_begin:jj_end), &260 1, iim,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id)260 call histbeg(name,nbp_lon,io_lon, jj_nb,io_lat(jj_begin:jj_end), & 261 1,nbp_lon,1,jj_nb,itau0, zjulian, dtime, nhori, nid_day,phys_domain_id) 261 262 endif 262 263 #endif … … 273 274 is_sequential, klon_mpi_begin, klon_mpi_end, & 274 275 mpi_rank 275 USE mod_grid_phy_lmdz, only: klon_glo 276 USE mod_grid_phy_lmdz, only: klon_glo, nbp_lon, nbp_lat, grid1dTo2d_glo 276 277 use ioipsl, only: histbeg 277 278 278 279 IMPLICIT NONE 279 include 'dimensions.h'280 280 281 281 REAL,DIMENSION(klon),INTENT(IN) :: rlon … … 303 303 REAL, allocatable, DIMENSION(:) :: npplat, npplon 304 304 REAL, allocatable, DIMENSION(:,:) :: npplat_bounds, npplon_bounds 305 INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm 306 REAL, DIMENSION(iim,jjmp1) :: zx_lon, zx_lat 305 REAL, DIMENSION(nbp_lon,nbp_lat) :: zx_lon, zx_lat 307 306 308 307 CALL gather(rlat,rlat_glo) … … 329 328 endif 330 329 ! 331 IF ( tabij(i).LE. iim) THEN330 IF ( tabij(i).LE.nbp_lon) THEN 332 331 plat_bounds(i,1)=rlat_glo(tabij(i)) 333 332 ELSE 334 plat_bounds(i,1)=rlat_glo(tabij(i)- iim)333 plat_bounds(i,1)=rlat_glo(tabij(i)-nbp_lon) 335 334 ENDIF 336 plat_bounds(i,2)=rlat_glo(tabij(i)+ iim)335 plat_bounds(i,2)=rlat_glo(tabij(i)+nbp_lon) 337 336 ! 338 337 ! print*,'CFMIP_iophy point i lon lon_bds',i,plon_bounds(i,1),rlon_glo(tabij(i)),plon_bounds(i,2) … … 350 349 ENDDO 351 350 352 CALL gr _fi_ecrit(1,klon,iim,jjmp1,rlon_glo,zx_lon)353 if ((iim*jjm).gt.1) then354 DO i = 1, iim355 zx_lon(i,1) = rlon_glo(i+1)356 zx_lon(i,jjmp1) = rlon_glo(i+1)357 ENDDO358 endif359 CALL gr _fi_ecrit(1,klon,iim,jjmp1,rlat_glo,zx_lat)351 CALL grid1dTo2d_glo(rlon_glo,zx_lon) 352 IF ( nbp_lon*nbp_lat > 1) then 353 DO i = 1, nbp_lon 354 zx_lon(i,1) = rlon_glo(i+1) 355 zx_lon(i,nbp_lat) = rlon_glo(i+1) 356 ENDDO 357 ENDIF 358 CALL grid1dTo2d_glo(rlat_glo,zx_lat) 360 359 361 360 DO i=1,pim … … 366 365 367 366 if (ipt(i).EQ.1) then 368 plon_bounds(i,1)=zx_lon( iim,jpt(i))367 plon_bounds(i,1)=zx_lon(nbp_lon,jpt(i)) 369 368 plon_bounds(i,2)=360.+zx_lon(ipt(i)+1,jpt(i)) 370 369 endif 371 370 372 if (ipt(i).EQ. iim) then371 if (ipt(i).EQ.nbp_lon) then 373 372 plon_bounds(i,2)=360.+zx_lon(1,jpt(i)) 374 373 endif … … 382 381 endif 383 382 384 if (jpt(i).EQ. jjmp1) then385 plat_bounds(i,1)=zx_lat(ipt(i), jjmp1)+0.001386 plat_bounds(i,2)=zx_lat(ipt(i), jjmp1)-0.001383 if (jpt(i).EQ.nbp_lat) then 384 plat_bounds(i,1)=zx_lat(ipt(i),nbp_lat)+0.001 385 plat_bounds(i,2)=zx_lat(ipt(i),nbp_lat)-0.001 387 386 endif 388 387 ! … … 444 443 445 444 446 SUBROUTINE histdef2d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar)447 448 USE ioipsl, only: histdef449 USE mod_phys_lmdz_para, only: jj_nb450 use phys_output_var_mod, only: type_ecri, zoutm, zdtime_moy, lev_files, &451 nid_files, nhorim, swaero_diag, nfiles452 IMPLICIT NONE453 INCLUDE "dimensions.h"454 INCLUDE "clesphys.h"455 456 INTEGER :: iff457 LOGICAL :: lpoint458 INTEGER, DIMENSION(nfiles) :: flag_var459 CHARACTER(LEN=20) :: nomvar460 CHARACTER(LEN=*) :: titrevar461 CHARACTER(LEN=*) :: unitvar462 463 REAL zstophym464 465 IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN466 zstophym=zoutm(iff)467 ELSE468 zstophym=zdtime_moy469 ENDIF470 471 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def472 CALL conf_physoutputs(nomvar,flag_var)473 474 IF(.NOT.lpoint) THEN475 IF ( flag_var(iff)<=lev_files(iff) ) THEN476 CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &477 iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &478 type_ecri(iff), zstophym,zoutm(iff))479 ENDIF480 ELSE481 IF ( flag_var(iff)<=lev_files(iff) ) THEN482 CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, &483 npstn,1,nhorim(iff), 1,1,1, -99, 32, &484 type_ecri(iff), zstophym,zoutm(iff))485 ENDIF486 ENDIF487 488 ! Set swaero_diag=true if at least one of the concerned variables are defined489 IF (nomvar=='topswad' .OR. nomvar=='topswai' .OR. nomvar=='solswad' .OR. nomvar=='solswai' ) THEN490 IF ( flag_var(iff)<=lev_files(iff) ) THEN491 swaero_diag=.TRUE.492 END IF493 END IF494 END SUBROUTINE histdef2d_old495 496 497 498 SUBROUTINE histdef3d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar)499 500 USE ioipsl, only: histdef501 USE dimphy, only: klev502 USE mod_phys_lmdz_para, only: jj_nb503 use phys_output_var_mod, only: type_ecri, zoutm, lev_files, nid_files, &504 nhorim, zdtime_moy, levmin, levmax, &505 nvertm, nfiles506 IMPLICIT NONE507 508 INCLUDE "dimensions.h"509 ! INCLUDE "indicesol.h"510 INCLUDE "clesphys.h"511 512 INTEGER :: iff513 LOGICAL :: lpoint514 INTEGER, DIMENSION(nfiles) :: flag_var515 CHARACTER(LEN=20) :: nomvar516 CHARACTER(LEN=*) :: titrevar517 CHARACTER(LEN=*) :: unitvar518 519 REAL zstophym520 521 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def522 CALL conf_physoutputs(nomvar,flag_var)523 524 IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN525 zstophym=zoutm(iff)526 ELSE527 zstophym=zdtime_moy528 ENDIF529 530 IF(.NOT.lpoint) THEN531 IF ( flag_var(iff)<=lev_files(iff) ) THEN532 CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, &533 iim, jj_nb, nhorim(iff), klev, levmin(iff), &534 levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), &535 zstophym, zoutm(iff))536 ENDIF537 ELSE538 IF ( flag_var(iff)<=lev_files(iff) ) THEN539 CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, &540 npstn,1,nhorim(iff), klev, levmin(iff), &541 levmax(iff)-levmin(iff)+1, nvertm(iff), 32, &542 type_ecri(iff), zstophym,zoutm(iff))543 ENDIF544 ENDIF545 END SUBROUTINE histdef3d_old546 547 548 549 550 551 552 553 445 554 446 SUBROUTINE histdef2d (iff,var) … … 559 451 clef_stations, phys_out_filenames, lev_files, & 560 452 nid_files, nhorim, swaero_diag 453 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 561 454 #ifdef CPP_XIOS 562 455 use wxios, only: wxios_add_field_to_file … … 564 457 IMPLICIT NONE 565 458 566 INCLUDE "dimensions.h"567 459 INCLUDE "clesphys.h" 568 460 … … 615 507 IF ( var%flag(iff)<=lev_files(iff) ) THEN 616 508 CALL histdef (nid_files(iff), var%name, var%description, var%unit, & 617 iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, &509 nbp_lon,jj_nb,nhorim(iff), 1,1,1, -99, 32, & 618 510 typeecrit, zstophym,zoutm(iff)) 619 511 ENDIF … … 644 536 nid_files, nhorim, swaero_diag, levmin, & 645 537 levmax, nvertm 538 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 646 539 #ifdef CPP_XIOS 647 540 use wxios, only: wxios_add_field_to_file 648 541 #endif 649 542 IMPLICIT NONE 650 651 INCLUDE "dimensions.h"652 543 INCLUDE "clesphys.h" 653 544 … … 700 591 IF ( var%flag(iff)<=lev_files(iff) ) THEN 701 592 CALL histdef (nid_files(iff), var%name, var%description, var%unit, & 702 iim, jj_nb, nhorim(iff), klev, levmin(iff), &593 nbp_lon, jj_nb, nhorim(iff), klev, levmin(iff), & 703 594 levmax(iff)-levmin(iff)+1, nvertm(iff), 32, typeecrit, & 704 595 zstophym, zoutm(iff)) … … 742 633 USE ioipsl, only: histwrite 743 634 USE inifis_mod, ONLY: prt_level, lunout 635 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 744 636 IMPLICIT NONE 745 include 'dimensions.h'746 637 747 638 integer,INTENT(IN) :: nid … … 752 643 REAL,DIMENSION(klon_mpi) :: buffer_omp 753 644 INTEGER, allocatable, DIMENSION(:) :: index2d 754 REAL :: Field2d( iim,jj_nb)645 REAL :: Field2d(nbp_lon,jj_nb) 755 646 756 647 integer :: ip … … 764 655 CALL grid1Dto2D_mpi(buffer_omp,Field2d) 765 656 if(.NOT.lpoint) THEN 766 ALLOCATE(index2d( iim*jj_nb))767 ALLOCATE(fieldok( iim*jj_nb))657 ALLOCATE(index2d(nbp_lon*jj_nb)) 658 ALLOCATE(fieldok(nbp_lon*jj_nb)) 768 659 IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL' 769 CALL histwrite(nid,name,itau,Field2d, iim*jj_nb,index2d)660 CALL histwrite(nid,name,itau,Field2d,nbp_lon*jj_nb,index2d) 770 661 IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL' 771 662 else … … 805 696 is_sequential, klon_mpi_begin, klon_mpi_end, & 806 697 jj_nb, klon_mpi 698 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 807 699 use ioipsl, only: histwrite 808 700 use inifis_mod, only: prt_level, lunout 809 701 IMPLICIT NONE 810 include 'dimensions.h'811 702 812 703 integer,INTENT(IN) :: nid … … 816 707 REAL,DIMENSION(:,:),INTENT(IN) :: field ! --> field(klon,:) 817 708 REAL,DIMENSION(klon_mpi,size(field,2)) :: buffer_omp 818 REAL :: Field3d( iim,jj_nb,size(field,2))709 REAL :: Field3d(nbp_lon,jj_nb,size(field,2)) 819 710 INTEGER :: ip, n, nlev 820 711 INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d … … 829 720 CALL grid1Dto2D_mpi(buffer_omp,field3d) 830 721 if(.NOT.lpoint) THEN 831 ALLOCATE(index3d( iim*jj_nb*nlev))832 ALLOCATE(fieldok( iim*jj_nb,nlev))722 ALLOCATE(index3d(nbp_lon*jj_nb*nlev)) 723 ALLOCATE(fieldok(nbp_lon*jj_nb,nlev)) 833 724 IF (prt_level >= 10) write(lunout,*)'Sending ',name,' to IOIPSL' 834 CALL histwrite(nid,name,itau,Field3d, iim*jj_nb*nlev,index3d)725 CALL histwrite(nid,name,itau,Field3d,nbp_lon*jj_nb*nlev,index3d) 835 726 IF (prt_level >= 10) write(lunout,*)'Finished sending ',name,' to IOIPSL' 836 727 else … … 880 771 nfiles, vars_defined, clef_stations, & 881 772 nid_files 773 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 882 774 #ifdef CPP_XIOS 883 775 USE xios, only: xios_send_field … … 886 778 887 779 IMPLICIT NONE 888 INCLUDE 'dimensions.h'889 780 include 'clesphys.h' 890 781 … … 899 790 REAL,DIMENSION(klon_mpi) :: buffer_omp 900 791 INTEGER, allocatable, DIMENSION(:) :: index2d 901 REAL :: Field2d( iim,jj_nb)792 REAL :: Field2d(nbp_lon,jj_nb) 902 793 903 794 INTEGER :: ip … … 980 871 981 872 IF(.NOT.clef_stations(iff)) THEN 982 ALLOCATE(index2d( iim*jj_nb))983 ALLOCATE(fieldok( iim*jj_nb))873 ALLOCATE(index2d(nbp_lon*jj_nb)) 874 ALLOCATE(fieldok(nbp_lon*jj_nb)) 984 875 #ifndef CPP_IOIPSL_NO_OUTPUT 985 CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d, iim*jj_nb,index2d)876 CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,nbp_lon*jj_nb,index2d) 986 877 #endif 987 878 !#ifdef CPP_XIOS … … 1039 930 nfiles, vars_defined, clef_stations, & 1040 931 nid_files 932 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 1041 933 #ifdef CPP_XIOS 1042 934 USE xios, only: xios_send_field … … 1045 937 1046 938 IMPLICIT NONE 1047 INCLUDE 'dimensions.h'1048 939 include 'clesphys.h' 1049 940 … … 1056 947 !$OMP THREADPRIVATE(firstx) 1057 948 REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp 1058 REAL :: Field3d( iim,jj_nb,SIZE(field,2))949 REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2)) 1059 950 INTEGER :: ip, n, nlev, nlevx 1060 951 INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d … … 1121 1012 iff,nlev,klev, firstx 1122 1013 write(lunout,*)'histwrite3d_phy: call xios_send_field for ', & 1123 trim(var%name), ' with iim jjmnlevx = ', &1124 iim,jj_nb,nlevx1014 trim(var%name), ' with nbp_lon nbp_lat nlevx = ', & 1015 nbp_lon,jj_nb,nlevx 1125 1016 endif 1126 1017 CALL xios_send_field(var%name, Field3d(:,:,1:nlevx)) … … 1129 1020 #endif 1130 1021 IF (.NOT.clef_stations(iff)) THEN 1131 ALLOCATE(index3d( iim*jj_nb*nlev))1132 ALLOCATE(fieldok( iim*jj_nb,nlev))1022 ALLOCATE(index3d(nbp_lon*jj_nb*nlev)) 1023 ALLOCATE(fieldok(nbp_lon*jj_nb,nlev)) 1133 1024 1134 1025 #ifndef CPP_IOIPSL_NO_OUTPUT 1135 CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d, iim*jj_nb*nlev,index3d)1026 CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,nbp_lon*jj_nb*nlev,index3d) 1136 1027 #endif 1137 1028 … … 1185 1076 is_sequential, klon_mpi_begin, klon_mpi_end, & 1186 1077 jj_nb, klon_mpi 1078 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 1187 1079 USE xios, only: xios_send_field 1188 1080 1189 1081 1190 1082 IMPLICIT NONE 1191 INCLUDE 'dimensions.h'1192 1083 1193 1084 CHARACTER(LEN=*), INTENT(IN) :: field_name … … 1196 1087 REAL,DIMENSION(klon_mpi) :: buffer_omp 1197 1088 INTEGER, allocatable, DIMENSION(:) :: index2d 1198 REAL :: Field2d( iim,jj_nb)1089 REAL :: Field2d(nbp_lon,jj_nb) 1199 1090 1200 1091 INTEGER :: ip … … 1215 1106 !IF(.NOT.clef_stations(iff)) THEN 1216 1107 IF (.TRUE.) THEN 1217 ALLOCATE(index2d( iim*jj_nb))1218 ALLOCATE(fieldok( iim*jj_nb))1108 ALLOCATE(index2d(nbp_lon*jj_nb)) 1109 ALLOCATE(fieldok(nbp_lon*jj_nb)) 1219 1110 1220 1111 … … 1256 1147 jj_nb, klon_mpi 1257 1148 USE xios, only: xios_send_field 1149 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 1258 1150 1259 1151 1260 1152 IMPLICIT NONE 1261 INCLUDE 'dimensions.h'1262 1153 1263 1154 CHARACTER(LEN=*), INTENT(IN) :: field_name … … 1265 1156 1266 1157 REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp 1267 REAL :: Field3d( iim,jj_nb,SIZE(field,2))1158 REAL :: Field3d(nbp_lon,jj_nb,SIZE(field,2)) 1268 1159 INTEGER :: ip, n, nlev 1269 1160 INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d … … 1286 1177 !IF (.NOT.clef_stations(iff)) THEN 1287 1178 IF(.TRUE.)THEN 1288 ALLOCATE(index3d( iim*jj_nb*nlev))1289 ALLOCATE(fieldok( iim*jj_nb,nlev))1179 ALLOCATE(index3d(nbp_lon*jj_nb*nlev)) 1180 ALLOCATE(fieldok(nbp_lon*jj_nb,nlev)) 1290 1181 CALL xios_send_field(field_name, Field3d(:,:,1:nlev)) 1291 1182 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/o3_chem_m.F90
r3816 r3819 14 14 15 15 ! All the 2-dimensional arrays are on the partial "physics" grid. 16 ! Their shape is "(/klon, llm/)".16 ! Their shape is "(/klon, klev/)". 17 17 ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)". 18 19 18 use assert_m, only: assert 20 use dimphy, only: klon 19 use dimphy, only: klon,klev 21 20 use regr_pr_comb_coefoz_m, only: c_Mob, a4_mass, a2, r_het_interm 22 21 ! use comconst_phy_mod … … 25 24 integer, intent(in):: julien ! jour julien, 1 <= julien <= 360 26 25 real, intent(in):: gmtime ! heure de la journée en fraction de jour 27 real, intent(in):: t_seri(:, :) ! (klon, llm) temperature, in K26 real, intent(in):: t_seri(:, :) ! (klon, klev) temperature, in K 28 27 29 real, intent(in):: zmasse(:, :) ! (klon, llm)28 real, intent(in):: zmasse(:, :) ! (klon, klev) 30 29 ! (column-density of mass of air in a cell, in kg m-2) 31 30 ! "zmasse(:, k)" is for layer "k".) … … 36 35 ! (longitude and latitude of each horizontal position, in degrees) 37 36 38 real, intent(inout):: q(:, :) ! (klon, llm) mass fraction of ozone37 real, intent(inout):: q(:, :) ! (klon, klev) mass fraction of ozone 39 38 ! "q(:, k)" is at middle of layer "k".) 40 39 41 40 ! Variables local to the procedure: 42 include "dimensions.h"43 41 ! (for "pi") 44 42 integer k 45 43 46 real c(klon, llm)44 real c(klon, klev) 47 45 ! (constant term during a time step in the net mass production 48 46 ! rate of ozone by chemistry, per unit mass of air, in s-1) 49 47 ! "c(:, k)" is at middle of layer "k".) 50 48 51 real b(klon, llm)49 real b(klon, klev) 52 50 ! (coefficient of "q" in the net mass production 53 51 ! rate of ozone by chemistry, per unit mass of air, in s-1) 54 52 ! "b(:, k)" is at middle of layer "k".) 55 53 56 real dq_o3_chem(klon, llm)54 real dq_o3_chem(klon, klev) 57 55 ! (variation of ozone mass fraction due to chemistry during a time step) 58 56 ! "dq_o3_chem(:, k)" is at middle of layer "k".) … … 70 68 call assert(klon == (/size(q, 1), size(t_seri, 1), size(zmasse, 1), & 71 69 size(rlat), size(rlon)/), "o3_chem klon") 72 call assert( llm== (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), &73 "o3_chem llm")70 call assert(klev == (/size(q, 2), size(t_seri, 2), size(zmasse, 2)/), & 71 "o3_chem klev") 74 72 75 73 c = c_Mob + a4_mass * t_seri … … 87 85 call orbite(real(julien), earth_long, trash1) 88 86 call zenang(earth_long, gmtime, pdtphys, rlat, rlon, pmu0, trash2) 89 forall (k = 1: llm)87 forall (k = 1: klev) 90 88 where (pmu0 <= cos(87. / 180. * pi)) b(:, k) = 0. 91 89 end forall … … 113 111 114 112 ! All the 2-dimensional arrays are on the partial "physics" grid. 115 ! Their shape is "(/klon, llm/)".113 ! Their shape is "(/klon, klev/)". 116 114 ! Index "(i, :)" is for longitude "rlon(i)", latitude "rlat(i)". 117 115 118 116 use regr_pr_comb_coefoz_m, only: a6_mass 119 117 use assert_m, only: assert 120 use dimphy, only: klon 118 use dimphy, only: klon, klev 121 119 122 120 real, intent(in):: q(:, :) ! mass fraction of ozone … … 137 135 ! ("b(:, k)" is at middle of layer "k".) 138 136 139 include "dimensions.h"140 137 141 real o3_prod(klon, llm)138 real o3_prod(klon, klev) 142 139 ! (net mass production rate of ozone by chemistry, per unit mass 143 140 ! of air, in s-1) … … 146 143 ! Variables local to the procedure: 147 144 148 real sigma_mass(klon, llm)145 real sigma_mass(klon, klev) 149 146 ! (mass column-density of ozone above point, in kg m-2) 150 147 ! ("sigma_mass(:, k)" is at middle of layer "k".) … … 156 153 call assert(klon == (/size(q, 1), size(zmasse, 1), size(c, 1), & 157 154 size(b, 1)/), "o3_prod 1") 158 call assert( llm== (/size(q, 2), size(zmasse, 2), size(c, 2), &155 call assert(klev == (/size(q, 2), size(zmasse, 2), size(c, 2), & 159 156 size(b, 2)/), "o3_prod 2") 160 157 … … 162 159 ! "k", and, as a first approximation, take it as column-density 163 160 ! above the middle of layer "k": 164 sigma_mass(:, llm) = zmasse(:, llm) * q(:, llm) ! top layer165 do k = llm- 1, 1, -1161 sigma_mass(:, klev) = zmasse(:, klev) * q(:, klev) ! top layer 162 do k = klev - 1, 1, -1 166 163 sigma_mass(:, k) = sigma_mass(:, k+1) + zmasse(:, k) * q(:, k) 167 164 end do -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/pbl_surface_mod.F90
r3818 r3819 263 263 ! USE temps_phy_mod 264 264 USE inifis_mod, ONLY: annee_ref, day_ini, itau_phy, lunout, prt_level 265 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat 265 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, grid1dto2d_glo 266 266 IMPLICIT NONE 267 267 … … 793 793 idayref = day_ini 794 794 CALL ymds2ju(annee_ref, 1, idayref, 0.0, zjulian) 795 CALL gr _fi_ecrit(1,klon,nbp_lon,nbp_lat,rlon,zx_lon)795 CALL grid1dTo2d_glo(rlon,zx_lon) 796 796 DO i = 1, nbp_lon 797 797 zx_lon(i,1) = rlon(i+1) 798 798 zx_lon(i,nbp_lat) = rlon(i+1) 799 799 ENDDO 800 CALL gr _fi_ecrit(1,klon,nbp_lon,nbp_lat,rlat,zx_lat)800 CALL grid1dTo2d_glo(rlat,zx_lat) 801 801 CALL histbeg("sous_index",nbp_lon,zx_lon(:,1),nbp_lat,zx_lat(1,:), & 802 802 1,nbp_lon,1,nbp_lat, & -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_mod.F90
r3817 r3819 36 36 USE iophy 37 37 USE dimphy 38 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 38 39 USE infotrac_phy 39 40 USE ioipsl … … 56 57 57 58 IMPLICIT NONE 58 include "dimensions.h"59 59 include "clesphys.h" 60 60 include "thermcell.h" … … 70 70 REAL, DIMENSION(klon, klev+1), INTENT(IN) :: paprs 71 71 REAL, DIMENSION(klon,klev,nqtot), INTENT(IN):: qx, d_qx 72 REAL, DIMENSION(klon, llm), INTENT(IN) :: zmasse72 REAL, DIMENSION(klon, klev), INTENT(IN) :: zmasse 73 73 74 74 … … 107 107 CHARACTER(LEN=2) :: bb3 108 108 CHARACTER(LEN=6) :: type_ocean 109 INTEGER, DIMENSION( iim*jjmp1):: ndex2d110 INTEGER, DIMENSION( iim*jjmp1*klev) :: ndex3d109 INTEGER, DIMENSION(nbp_lon*jjmp1) :: ndex2d 110 INTEGER, DIMENSION(nbp_lon*jjmp1*klev) :: ndex3d 111 111 INTEGER :: imin_ins, imax_ins 112 112 INTEGER :: jmin_ins, jmax_ins … … 344 344 IF (phys_out_regfkey(iff)) then 345 345 imin_ins=1 346 imax_ins= iim346 imax_ins=nbp_lon 347 347 jmin_ins=1 348 348 jmax_ins=jjmp1 349 349 350 350 ! correction abderr 351 do i=1, iim351 do i=1,nbp_lon 352 352 WRITE(lunout,*)'io_lon(i)=',io_lon(i) 353 353 IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i … … 368 368 io_lat(jmax_ins),io_lat(jmin_ins) 369 369 370 CALL histbeg(phys_out_filenames(iff), iim,io_lon,jjmp1,io_lat, &370 CALL histbeg(phys_out_filenames(iff),nbp_lon,io_lon,jjmp1,io_lat, & 371 371 imin_ins,imax_ins-imin_ins+1, & 372 372 jmin_ins,jmax_ins-jmin_ins+1, & -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/phys_output_write_mod.F90
r3817 r3819 25 25 26 26 USE dimphy, only: klon, klev, klevp1, nslay 27 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 27 28 !USE control_phy_mod, only: day_step, iphysiq 28 29 USE inifis_mod, only: day_step, iphysiq … … 258 259 INCLUDE "compbl.h" 259 260 INCLUDE "YOMCST.h" 260 INCLUDE "dimensions.h"261 261 262 262 ! Input … … 273 273 REAL, DIMENSION(klon, klev+1) :: paprs 274 274 REAL, DIMENSION(klon,klev,nqtot) :: qx, d_qx 275 REAL, DIMENSION(klon, llm) :: zmasse275 REAL, DIMENSION(klon, klev) :: zmasse 276 276 LOGICAL :: flag_aerosol_strat 277 277 INTEGER :: flag_aerosol … … 280 280 281 281 ! Local 282 INTEGER, PARAMETER :: jjmp1=jjm+1-1/jjm283 282 INTEGER :: itau_w 284 283 INTEGER :: i, iinit, iinitend=1, iff, iq, nsrf, k, ll, naero … … 287 286 REAL, DIMENSION (klon,klev+1) :: zx_tmp_fi3d1 288 287 CHARACTER (LEN=4) :: bb2 289 INTEGER, DIMENSION( iim*jjmp1) :: ndex2d290 INTEGER, DIMENSION( iim*jjmp1*klev) :: ndex3d288 INTEGER, DIMENSION(nbp_lon*nbp_lat) :: ndex2d 289 INTEGER, DIMENSION(nbp_lon*nbp_lat*klev) :: ndex3d 291 290 REAL, PARAMETER :: dobson_u = 2.1415e-05 ! Dobson unit, in kg m-2 292 291 REAL, PARAMETER :: missing_val=nf90_fill_real -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/physiq.F90
r3818 r3819 18 18 USE dimphy 19 19 USE infotrac_phy 20 USE mod_grid_phy_lmdz21 20 USE mod_phys_lmdz_para 22 21 USE iophy … … 51 50 annee_ref, day_ref, itau_phy, jD_ref, start_time, & 52 51 prt_level, lunout 53 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev 52 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev, grid1dTo2d_glo, klon_glo 54 53 #ifdef REPROBUS 55 54 USE CHEM_REP, ONLY : Init_chem_rep_xjour … … 4294 4293 RETURN 4295 4294 END FUNCTION qcheck 4296 SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit)4297 IMPLICIT none4298 !4299 ! Tranformer une variable de la grille physique a4300 ! la grille d'ecriture4301 !4302 INTEGER nfield,nlon,iim,jjmp1, jjm4303 REAL fi(nlon,nfield), ecrit(iim*jjmp1,nfield)4304 !4305 INTEGER i, n, ig4306 !4307 jjm = jjmp1 - 14308 DO n = 1, nfield4309 DO i=1,iim4310 ecrit(i,n) = fi(1,n)4311 ecrit(i+jjm*iim,n) = fi(nlon,n)4312 ENDDO4313 DO ig = 1, nlon - 24314 ecrit(iim+ig,n) = fi(1+ig,n)4315 ENDDO4316 ENDDO4317 RETURN4318 END SUBROUTINE gr_fi_ecrit4319 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosol.F90
r3817 r3819 178 178 ! 3) Read field month by month 179 179 ! 4) Close file 180 ! 5) Transform the global field from 2D( iim, jjp+1) to 1D(klon_glo)180 ! 5) Transform the global field from 2D(nbp_lon, jjp+1) to 1D(klon_glo) 181 181 ! - Also the levels and the latitudes have to be inversed 182 182 ! … … 194 194 195 195 IMPLICIT NONE 196 197 INCLUDE "dimensions.h"198 196 199 197 ! Input argumets … … 223 221 REAL, ALLOCATABLE, DIMENSION(:) :: varktmp 224 222 225 REAL, DIMENSION( iim,jjm+1,12):: psurf_glo2D ! Surface pression for 12 months on dynamics global grid223 REAL, DIMENSION(nbp_lon,nbp_lat,12) :: psurf_glo2D ! Surface pression for 12 months on dynamics global grid 226 224 REAL, DIMENSION(klon_glo,12) :: psurf_glo1D ! -"- on physical global grid 227 REAL, DIMENSION( iim,jjm+1,12):: load_glo2D ! Load for 12 months on dynamics global grid225 REAL, DIMENSION(nbp_lon,nbp_lat,12) :: load_glo2D ! Load for 12 months on dynamics global grid 228 226 REAL, DIMENSION(klon_glo,12) :: load_glo1D ! -"- on physical global grid 229 REAL, DIMENSION( iim,jjm+1):: vartmp230 REAL, DIMENSION( iim):: lon_src ! longitudes in file231 REAL, DIMENSION( jjm+1):: lat_src, lat_src_inv ! latitudes in file227 REAL, DIMENSION(nbp_lon,nbp_lat) :: vartmp 228 REAL, DIMENSION(nbp_lon) :: lon_src ! longitudes in file 229 REAL, DIMENSION(nbp_lat) :: lat_src, lat_src_inv ! latitudes in file 232 230 LOGICAL :: new_file ! true if new file format detected 233 231 LOGICAL :: invert_lat ! true if the field has to be inverted for latitudes … … 267 265 268 266 ! Invert source latitudes 269 DO j = 1, jjm+1270 lat_src_inv(j) = lat_src( jjm+1+1 -j)267 DO j = 1, nbp_lat 268 lat_src_inv(j) = lat_src(nbp_lat +1 -j) 271 269 END DO 272 270 … … 313 311 314 312 ! Allocate variables depending on the number of vertical levels 315 ALLOCATE(varmth( iim, jjm+1, klev_src), varyear(iim, jjm+1, klev_src, 12), stat=ierr)313 ALLOCATE(varmth(nbp_lon, nbp_lat, klev_src), varyear(nbp_lon, nbp_lat, klev_src, 12), stat=ierr) 316 314 IF (ierr /= 0) CALL abort_physic('get_aero_fromfile', 'pb in allocation 1',1) 317 315 … … 435 433 436 434 437 ! 5) Transform the global field from 2D( iim, jjp+1) to 1D(klon_glo)435 ! 5) Transform the global field from 2D(nbp_lon, jjp+1) to 1D(klon_glo) 438 436 !**************************************************************************************** 439 437 ! Test if vertical levels have to be inversed … … 448 446 varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly 449 447 DO k=1, klev_src 450 DO j=1, jjm+1451 DO i=1, iim448 DO j=1, nbp_lat 449 DO i=1,nbp_lon 452 450 varyear(i,j,k,imth) = varmth(i,j,klev_src+1-k) 453 451 END DO … … 482 480 varmth(:,:,:) = varyear(:,:,:,imth) ! use varmth temporarly 483 481 DO k=1,klev_src 484 DO j=1, jjm+1485 DO i=1, iim486 varyear(i,j,k,imth) = varmth(i, jjm+1+1-j,k)482 DO j=1,nbp_lat 483 DO i=1,nbp_lon 484 varyear(i,j,k,imth) = varmth(i,nbp_lat+1-j,k) 487 485 END DO 488 486 END DO … … 491 489 ! Invert latitudes for surface pressure 492 490 vartmp(:,:) = psurf_glo2D(:,:,imth) 493 DO j=1, jjm+1494 DO i=1, iim495 psurf_glo2D(i,j,imth)= vartmp(i, jjm+1+1-j)491 DO j=1, nbp_lat 492 DO i=1,nbp_lon 493 psurf_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j) 496 494 END DO 497 495 END DO … … 499 497 ! Invert latitudes for the load 500 498 vartmp(:,:) = load_glo2D(:,:,imth) 501 DO j=1, jjm+1502 DO i=1, iim503 load_glo2D(i,j,imth)= vartmp(i, jjm+1+1-j)499 DO j=1, nbp_lat 500 DO i=1,nbp_lon 501 load_glo2D(i,j,imth)= vartmp(i,nbp_lat+1-j) 504 502 END DO 505 503 END DO … … 509 507 DO k=1, klev_src 510 508 npole=0. ! North pole, j=1 511 spole=0. ! South pole, j= jjm+1512 DO i=1, iim509 spole=0. ! South pole, j=nbp_lat 510 DO i=1,nbp_lon 513 511 npole = npole + varyear(i,1,k,imth) 514 spole = spole + varyear(i, jjm+1,k,imth)512 spole = spole + varyear(i,nbp_lat,k,imth) 515 513 END DO 516 npole = npole/REAL( iim)517 spole = spole/REAL( iim)514 npole = npole/REAL(nbp_lon) 515 spole = spole/REAL(nbp_lon) 518 516 varyear(:,1, k,imth) = npole 519 varyear(:, jjm+1,k,imth) = spole517 varyear(:,nbp_lat,k,imth) = spole 520 518 END DO 521 519 END DO ! imth -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosol_interp.F90
r3817 r3819 28 28 INCLUDE "chem.h" 29 29 INCLUDE "clesphys.h" 30 INCLUDE "dimensions.h"31 30 ! 32 31 ! Input: -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readaerosolstrato.F90
r3809 r3819 6 6 7 7 USE phys_cal_mod, ONLY : mth_cur 8 USE mod_grid_phy_lmdz 8 USE mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat, klon_glo, grid2dTo1d_glo 9 9 USE mod_phys_lmdz_mpi_data, ONLY : is_mpi_root 10 10 USE mod_phys_lmdz_para … … 17 17 18 18 include "YOMCST.h" 19 include "dimensions.h"20 19 21 20 ! Variable input … … 85 84 n_lat = size(latitude) 86 85 print *, 'LAT aerosol strato=', n_lat, latitude 87 IF (n_lat.NE. jjm+1) THEN88 print *,'Le nombre de lat n est pas egal a jjm+1'86 IF (n_lat.NE.nbp_lat) THEN 87 print *,'Le nombre de lat n est pas egal a nbp_lat' 89 88 STOP 90 89 ENDIF … … 94 93 n_lon = size(longitude) 95 94 print *, 'LON aerosol strato=', n_lon, longitude 96 IF (n_lon.NE. iim) THEN97 print *,'Le nombre de lon n est pas egal a iim'95 IF (n_lon.NE.nbp_lon) THEN 96 print *,'Le nombre de lon n est pas egal a nbp_lon' 98 97 STOP 99 98 ENDIF -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/readchlorophyll.F90
r3809 r3819 20 20 21 21 include "YOMCST.h" 22 include "dimensions.h"23 22 24 23 ! Variable input … … 62 61 n_lon = size(longitude) 63 62 ! print *, 'LON chlorophyll=', n_lon, longitude 64 IF (n_lon.NE. iim) THEN65 print *,'Le nombre de lon n est pas egal a iim'63 IF (n_lon.NE.nbp_lon) THEN 64 print *,'Le nombre de lon n est pas egal a nbp_lon' 66 65 STOP 67 66 ENDIF … … 72 71 n_lat = size(latitude) 73 72 ! print *, 'LAT chlorophyll=', n_lat, latitude 74 IF (n_lat.NE. jjm+1) THEN75 print *,'Le nombre de lat n est pas egal a jjm+1'73 IF (n_lat.NE.nbp_lat) THEN 74 print *,'Le nombre de lat n est pas egal a nbp_lat' 76 75 STOP 77 76 ENDIF -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_climoz_m.F90
r3816 r3819 65 65 ! periodicity for interpolation at the beginning and at the end of the 66 66 ! year. 67 67 use mod_grid_phy_lmdz, ONLY : nbp_lat 68 68 use regr1_step_av_m, only: regr1_step_av 69 69 use regr3_lint_m, only: regr3_lint … … 85 85 ! Variables local to the procedure: 86 86 87 include "dimensions.h"88 ! (for "jjm")89 90 87 integer n_plev ! number of pressure levels in the input data 91 88 integer n_lat ! number of latitudes in the input data … … 118 115 119 116 real, allocatable:: o3_regr_lat(:, :, :, :) 120 ! ( jjm + 1, n_plev, 0:13, read_climoz)117 ! (nbp_lat, n_plev, 0:13, read_climoz) 121 118 ! mean of "o3_in" over a latitude interval of LMDZ 122 119 ! First dimension is latitude interval. 123 120 ! The latitude interval for "o3_regr_lat(j,:, :, :)" contains "rlatu(j)". 124 ! If "j" is between 2 and " jjm" then the interval is:121 ! If "j" is between 2 and "nbp_lat-1" then the interval is: 125 122 ! [rlatv(j), rlatv(j-1)] 126 ! If "j" is 1 or " jjm + 1" then the interval is:123 ! If "j" is 1 or "nbp_lat" then the interval is: 127 124 ! [rlatv(1), pi / 2] 128 125 ! or: 129 ! [- pi / 2, rlatv( jjm)]126 ! [- pi / 2, rlatv(nbp_lat-1)] 130 127 ! respectively. 131 128 ! "o3_regr_lat(:, k, :, :)" is for pressure level "plev(k)". … … 135 132 136 133 real, allocatable:: o3_out(:, :, :, :) 137 ! ( jjm + 1, n_plev, 360, read_climoz)134 ! (nbp_lat, n_plev, 360, read_climoz) 138 135 ! regridded ozone climatology 139 136 ! "o3_out(j, k, l, :)" is at latitude "rlatu(j)", pressure … … 286 283 call nf95_close(ncid_in) 287 284 288 allocate(o3_regr_lat( jjm + 1, n_plev, 0:13, read_climoz))289 allocate(o3_out( jjm + 1, n_plev, 360, read_climoz))285 allocate(o3_regr_lat(nbp_lat, n_plev, 0:13, read_climoz)) 286 allocate(o3_out(nbp_lat, n_plev, 360, read_climoz)) 290 287 291 288 ! Regrid in latitude: … … 295 292 print *, & 296 293 "Found 12 months in ozone climatologies, assuming periodicity..." 297 o3_regr_lat( jjm+1:1:-1, :, 1:12, :) = regr1_step_av(o3_in, &298 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv( jjm:1:-1), pi / 2/)))294 o3_regr_lat(nbp_lat:1:-1, :, 1:12, :) = regr1_step_av(o3_in, & 295 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(nbp_lat-1:1:-1), pi / 2/))) 299 296 ! (invert order of indices in "o3_regr_lat" because "rlatu" is 300 297 ! in descending order) … … 306 303 else 307 304 print *, "Using 14 months in ozone climatologies..." 308 o3_regr_lat( jjm+1:1:-1, :, :, :) = regr1_step_av(o3_in, &309 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv( jjm:1:-1), pi / 2/)))305 o3_regr_lat(nbp_lat:1:-1, :, :, :) = regr1_step_av(o3_in, & 306 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(nbp_lat-1:1:-1), pi / 2/))) 310 307 ! (invert order of indices in "o3_regr_lat" because "rlatu" is 311 308 ! in descending order) … … 317 314 ! Write to file: 318 315 do m = 1, read_climoz 319 call nf95_put_var(ncid_out, varid_out(m), o3_out( jjm+1:1:-1, :, :, m))316 call nf95_put_var(ncid_out, varid_out(m), o3_out(nbp_lat:1:-1, :, :, m)) 320 317 ! (The order of "rlatu" is inverted in the output file) 321 318 end do … … 333 330 ! dimensions and variables, and writes one of the coordinate variables. 334 331 332 use mod_grid_phy_lmdz, ONLY : nbp_lat 335 333 use netcdf95, only: nf95_create, nf95_def_dim, nf95_def_var, & 336 334 nf95_put_att, nf95_enddef, nf95_copy_att, nf95_put_var … … 349 347 ! Variables local to the procedure: 350 348 351 include "dimensions.h"352 353 349 integer ncerr 354 350 integer dimid_rlatu, dimid_plev, dimid_time … … 364 360 call nf95_def_dim(ncid_out, "time", 360, dimid_time) 365 361 call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev) 366 call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)362 call nf95_def_dim(ncid_out, "rlatu", nbp_lat, dimid_rlatu) 367 363 368 364 ! Define coordinate variables: … … 425 421 426 422 ! Write one of the coordinate variables: 427 call nf95_put_var(ncid_out, varid_rlatu, rlatu( jjm+1:1:-1) / pi * 180.)423 call nf95_put_var(ncid_out, varid_rlatu, rlatu(nbp_lat:1:-1) / pi * 180.) 428 424 ! (convert from rad to degrees and sort in ascending order) 429 425 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_lat_time_coefoz_m.F90
r3816 r3819 40 40 ! when we regrid in pressure). 41 41 42 use mod_grid_phy_lmdz, ONLY : nbp_lat 42 43 use regr1_step_av_m, only: regr1_step_av 43 44 use regr3_lint_m, only: regr3_lint … … 51 52 ! Variables local to the procedure: 52 53 53 include "dimensions.h"54 ! (for "jjm")55 56 54 integer ncid_in, ncid_out ! NetCDF IDs for input and output files 57 55 integer n_plev ! number of pressure levels in the input data … … 73 71 ! level "plev(l)". "month" is between 1 and 12.) 74 72 75 real, allocatable:: v_regr_lat(:, :, :) ! ( jjm + 1, n_plev, 0:13)73 real, allocatable:: v_regr_lat(:, :, :) ! (nbp_lat, n_plev, 0:13) 76 74 ! (mean of a variable "v" over a latitude interval) 77 75 ! (First dimension is latitude interval. 78 76 ! The latitude interval for "v_regr_lat(j,:, :)" contains "rlatu(j)". 79 ! If "j" is between 2 and " jjm" then the interval is:77 ! If "j" is between 2 and "nbp_lat-1" then the interval is: 80 78 ! [rlatv(j), rlatv(j-1)] 81 ! If "j" is 1 or " jjm + 1" then the interval is:79 ! If "j" is 1 or "nbp_lat" then the interval is: 82 80 ! [rlatv(1), pi / 2] 83 81 ! or: 84 ! [- pi / 2, rlatv( jjm)]82 ! [- pi / 2, rlatv(nbp_lat-1)] 85 83 ! respectively. 86 84 ! "v_regr_lat(:, l, :)" is for pressure level "plev(l)". 87 85 ! Last dimension is month number.) 88 86 89 real, allocatable:: o3_par_out(:, :, :) ! ( jjm + 1, n_plev, 360)87 real, allocatable:: o3_par_out(:, :, :) ! (nbp_lat, n_plev, 360) 90 88 ! (regridded ozone parameter) 91 89 ! ("o3_par_out(j, l, day)" is at latitude "rlatu(j)", pressure … … 198 196 199 197 allocate(o3_par_in(n_lat, n_plev, 12)) 200 allocate(v_regr_lat( jjm + 1, n_plev, 0:13))201 allocate(o3_par_out( jjm + 1, n_plev, 360))198 allocate(v_regr_lat(nbp_lat, n_plev, 0:13)) 199 allocate(o3_par_out(nbp_lat, n_plev, 360)) 202 200 203 201 do i_v = 1, n_o3_param … … 212 210 ! We average with respect to sine of latitude, which is 213 211 ! equivalent to weighting by cosine of latitude: 214 v_regr_lat( jjm+1:1:-1, :, 1:12) = regr1_step_av(o3_par_in, &215 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv( jjm:1:-1), pi / 2/)))212 v_regr_lat(nbp_lat:1:-1, :, 1:12) = regr1_step_av(o3_par_in, & 213 xs=sin(lat_in_edg), xt=sin((/- pi / 2, rlatv(nbp_lat-1:1:-1), pi / 2/))) 216 214 ! (invert order of indices in "v_regr_lat" because "rlatu" is 217 215 ! in descending order) … … 227 225 ! Write to file: 228 226 call nf95_put_var(ncid_out, varid_out(i_v), & 229 o3_par_out( jjm+1:1:-1, :, :))227 o3_par_out(nbp_lat:1:-1, :, :)) 230 228 ! (The order of "rlatu" is inverted in the output file) 231 229 end do … … 244 242 ! dimensions and variables, and writes one of the coordinate variables. 245 243 244 use mod_grid_phy_lmdz, ONLY : nbp_lat 246 245 use assert_eq_m, only: assert_eq 247 246 … … 260 259 ! Variables local to the procedure: 261 260 262 include "dimensions.h"263 ! (for "jjm")264 261 265 262 integer ncerr … … 279 276 call nf95_def_dim(ncid_out, "time", 360, dimid_time) 280 277 call nf95_def_dim(ncid_out, "plev", n_plev, dimid_plev) 281 call nf95_def_dim(ncid_out, "rlatu", jjm + 1, dimid_rlatu)278 call nf95_def_dim(ncid_out, "rlatu", nbp_lat, dimid_rlatu) 282 279 283 280 ! Define coordinate variables: … … 329 326 330 327 ! Write one of the coordinate variables: 331 call nf95_put_var(ncid_out, varid_rlatu, rlatu( jjm+1:1:-1) / pi * 180.)328 call nf95_put_var(ncid_out, varid_rlatu, rlatu(nbp_lat:1:-1) / pi * 180.) 332 329 ! (convert from rad to degrees and sort in ascending order) 333 330 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_av_m.F90
r3809 r3819 33 33 ! NetCDF variable. 34 34 35 use dimphy, only: klon 35 use dimphy, only: klon, klev 36 use mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 36 37 use netcdf95, only: nf95_inq_varid, handle_err 37 38 use netcdf, only: nf90_get_var … … 52 53 ! ascending order 53 54 54 real, intent(in):: paprs(:, :) ! (klon, llm+ 1)55 real, intent(in):: paprs(:, :) ! (klon, klev + 1) 55 56 ! (pression pour chaque inter-couche, en Pa) 56 57 57 real, intent(out):: v3(:, :, :) ! (klon, llm, size(name))58 real, intent(out):: v3(:, :, :) ! (klon, klev, size(name)) 58 59 ! regridded fields on the partial "physics" grid 59 60 ! "v3(i, k, l)" is at longitude "xlon(i)", latitude … … 63 64 ! Variables local to the procedure: 64 65 65 include "dimensions.h"66 66 integer varid, ncerr ! for NetCDF 67 67 68 real v1( iim, jjm + 1, size(press_in_edg) - 1, size(name))68 real v1(nbp_lon, nbp_lat, size(press_in_edg) - 1, size(name)) 69 69 ! input fields at day "julien", on the global "dynamics" horizontal grid 70 70 ! First dimension is for longitude. … … 84 84 !-------------------------------------------- 85 85 86 call assert(size(v3, 1) == klon, size(v3, 2) == llm, "regr_pr_av v3 klon")86 call assert(size(v3, 1) == klon, size(v3, 2) == klev, "regr_pr_av v3 klon") 87 87 n_var = assert_eq(size(name), size(v3, 3), "regr_pr_av v3 n_var") 88 call assert(shape(paprs) == (/klon, llm+1/), "regr_pr_av paprs")88 call assert(shape(paprs) == (/klon, klev+1/), "regr_pr_av paprs") 89 89 90 90 !$omp master … … 102 102 ! Latitudes are in ascending order in the input file while 103 103 ! "rlatu" is in descending order so we need to invert order: 104 v1(1, :, :, :) = v1(1, jjm+1:1:-1, :, :)104 v1(1, :, :, :) = v1(1, nbp_lat:1:-1, :, :) 105 105 106 106 ! Duplicate on all longitudes: 107 v1(2:, :, :, :) = spread(v1(1, :, :, :), dim=1, ncopies= iim-1)107 v1(2:, :, :, :) = spread(v1(1, :, :, :), dim=1, ncopies=nbp_lon-1) 108 108 end if 109 109 !$omp end master … … 113 113 ! Regrid in pressure at each horizontal position: 114 114 do i = 1, klon 115 v3(i, llm:1:-1, :) = regr1_step_av(v2(i, :, :), press_in_edg, &116 paprs(i, llm+1:1:-1))115 v3(i, klev:1:-1, :) = regr1_step_av(v2(i, :, :), press_in_edg, & 116 paprs(i, klev+1:1:-1)) 117 117 ! (invert order of indices because "paprs" is in descending order) 118 118 end do -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_comb_coefoz_m.F90
r3809 r3819 39 39 ! It allocates module variables. 40 40 41 use dimphy, only: klon 41 use dimphy, only: klon, klev 42 42 43 43 ! Variables local to the procedure: 44 include "dimensions.h"45 44 46 45 !--------------------------------------- … … 49 48 print *, "Call sequence information: alloc_coefoz" 50 49 !$omp end master 51 allocate(c_Mob(klon, llm), a2(klon, llm), a4_mass(klon, llm))52 allocate(a6_mass(klon, llm), r_het_interm(klon, llm))50 allocate(c_Mob(klon, klev), a2(klon, klev), a4_mass(klon, klev)) 51 allocate(a6_mass(klon, klev), r_het_interm(klon, klev)) 53 52 54 53 end subroutine alloc_coefoz … … 74 73 use netcdf, only: nf90_nowrite 75 74 use assert_m, only: assert 76 use dimphy, only: klon 75 use dimphy, only: klon, klev 77 76 use mod_phys_lmdz_mpi_data, only: is_mpi_root 78 77 use regr_pr_av_m, only: regr_pr_av … … 85 84 ! (latitude on the partial "physics" grid, in degrees) 86 85 87 real, intent(in):: paprs(:, :) ! (klon, llm+ 1)86 real, intent(in):: paprs(:, :) ! (klon, klev + 1) 88 87 ! (pression pour chaque inter-couche, en Pa) 89 88 90 real, intent(in):: pplay(:, :) ! (klon, llm)89 real, intent(in):: pplay(:, :) ! (klon, klev) 91 90 ! (pression pour le mileu de chaque couche, en Pa) 92 91 93 92 ! Variables local to the procedure: 94 93 95 include "dimensions.h"96 94 integer ncid ! for NetCDF 97 95 98 real coefoz(klon, llm, 7)96 real coefoz(klon, klev, 7) 99 97 ! (temporary storage for 7 ozone coefficients) 100 98 ! (On the partial "physics" grid. … … 102 100 ! middle of layer "k".) 103 101 104 real a6(klon, llm)102 real a6(klon, klev) 105 103 ! (derivative of "P_net_Mob" with respect to column-density of ozone 106 104 ! above, in cm2 s-1) … … 121 119 call assert((/size(rlat), size(paprs, 1), size(pplay, 1)/) == klon, & 122 120 "regr_pr_comb_coefoz klon") 123 call assert((/size(paprs, 2) - 1, size(pplay, 2)/) == llm, &124 "regr_pr_comb_coefoz llm")121 call assert((/size(paprs, 2) - 1, size(pplay, 2)/) == klev, & 122 "regr_pr_comb_coefoz klev") 125 123 126 124 !$omp master … … 150 148 r_het_interm = coefoz(:, :, 7) 151 149 ! Heterogeneous chemistry is only at high latitudes: 152 forall (k = 1: llm)150 forall (k = 1: klev) 153 151 where (abs(rlat) <= 45.) r_het_interm(:, k) = 0. 154 152 end forall -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_int_m.F90
r3809 r3819 24 24 ! Regridding is by linear interpolation. 25 25 26 use dimphy, only: klon 26 use dimphy, only: klon, klev 27 use mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 27 28 use netcdf95, only: nf95_inq_varid, handle_err 28 29 use netcdf, only: nf90_get_var … … 41 42 ! (pressure level of input data, in Pa, in strictly ascending order) 42 43 43 real, intent(in):: pplay(:, :) ! (klon, llm)44 real, intent(in):: pplay(:, :) ! (klon, klev) 44 45 ! (pression pour le mileu de chaque couche, en Pa) 45 46 … … 47 48 ! (extra value of field at 0 pressure) 48 49 49 real, intent(out):: v3(:, :) ! (klon, llm)50 real, intent(out):: v3(:, :) ! (klon, klev) 50 51 ! (regridded field on the partial "physics" grid) 51 52 ! ("v3(i, k)" is at longitude "xlon(i)", latitude … … 54 55 ! Variables local to the procedure: 55 56 56 include "dimensions.h"57 57 integer varid, ncerr ! for NetCDF 58 58 59 real v1( iim, jjm + 1, 0:size(plev))59 real v1(nbp_lon, nbp_lat, 0:size(plev)) 60 60 ! (input field at day "julien", on the global "dynamics" horizontal grid) 61 61 ! (First dimension is for longitude. … … 72 72 !-------------------------------------------- 73 73 74 call assert(shape(v3) == (/klon, llm/), "regr_pr_int v3")75 call assert(shape(pplay) == (/klon, llm/), "regr_pr_int pplay")74 call assert(shape(v3) == (/klon, klev/), "regr_pr_int v3") 75 call assert(shape(pplay) == (/klon, klev/), "regr_pr_int pplay") 76 76 77 77 !$omp master … … 84 84 ! Latitudes are in ascending order in the input file while 85 85 ! "rlatu" is in descending order so we need to invert order: 86 v1(1, :, 1:) = v1(1, jjm+1:1:-1, 1:)86 v1(1, :, 1:) = v1(1, nbp_lat:1:-1, 1:) 87 87 88 88 ! Complete "v1" with the value at 0 pressure: … … 90 90 91 91 ! Duplicate on all longitudes: 92 v1(2:, :, :) = spread(v1(1, :, :), dim=1, ncopies= iim-1)92 v1(2:, :, :) = spread(v1(1, :, :), dim=1, ncopies=nbp_lon-1) 93 93 end if 94 94 !$omp end master … … 98 98 ! Regrid in pressure at each horizontal position: 99 99 do i = 1, klon 100 v3(i, llm:1:-1) = regr1_lint(v2(i, :), (/0., plev/), pplay(i, llm:1:-1))100 v3(i, klev:1:-1) = regr1_lint(v2(i, :), (/0., plev/), pplay(i, klev:1:-1)) 101 101 ! (invert order of indices because "pplay" is in descending order) 102 102 end do -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/regr_pr_o3_m.F90
r3816 r3819 25 25 ! hPa and strictly increasing. 26 26 27 use dimphy, ONLY : klon, klev 28 use mod_grid_phy_lmdz, ONLY : nbp_lon, nbp_lat 27 29 use netcdf95, only: nf95_open, nf95_close, nf95_inq_varid, handle_err 28 30 use netcdf, only: nf90_nowrite, nf90_get_var … … 37 39 ! for interface "l") 38 40 39 real, intent(out):: o3_mob_regr(:, :, :) ! ( iim + 1, jjm + 1, llm)41 real, intent(out):: o3_mob_regr(:, :, :) ! (nbp_lon + 1, nbp_lat + 1, klev) 40 42 ! (ozone mole fraction from Mobidic adapted to the LMDZ grid) 41 43 ! ("o3_mob_regr(i, j, l)" is at longitude "rlonv(i)", latitude … … 44 46 ! Variables local to the procedure: 45 47 46 include "dimensions.h"47 48 48 49 integer ncid, varid, ncerr ! for NetCDF 49 50 integer i, j 50 51 51 real r_mob( jjm + 1, size(press_in_edg) - 1)52 real r_mob(nbp_lat, size(press_in_edg) - 1) 52 53 ! (ozone mole fraction from Mobidic at day "dayref") 53 54 ! (r_mob(j, k) is at latitude "rlatu(j)", in pressure interval … … 57 58 58 59 print *, "Call sequence information: regr_pr_o3" 59 call assert(shape(o3_mob_regr) == (/ iim + 1, jjm + 1, llm/), &60 call assert(shape(o3_mob_regr) == (/nbp_lon + 1, nbp_lat, klev/), & 60 61 "regr_pr_o3 o3_mob_regr") 61 call assert(shape(p3d) == (/ iim + 1, jjm + 1, llm+ 1/), "regr_pr_o3 p3d")62 call assert(shape(p3d) == (/nbp_lon + 1, nbp_lat, klev + 1/), "regr_pr_o3 p3d") 62 63 63 64 call nf95_open("coefoz_LMDZ.nc", nf90_nowrite, ncid) … … 69 70 ! Latitudes are in ascending order in the input file while 70 71 ! "rlatu" is in descending order so we need to invert order: 71 r_mob = r_mob( jjm+1:1:-1, :)72 r_mob = r_mob(nbp_lat:1:-1, :) 72 73 73 74 call nf95_close(ncid) … … 76 77 77 78 ! Poles: 78 do j = 1, jjm + 1, jjm79 o3_mob_regr(1, j, llm:1:-1) &80 = regr1_step_av(r_mob(j, :), press_in_edg, p3d(1, j, llm+1:1:-1))79 do j = 1, nbp_lat, nbp_lat-1 80 o3_mob_regr(1, j, klev:1:-1) & 81 = regr1_step_av(r_mob(j, :), press_in_edg, p3d(1, j, klev+1:1:-1)) 81 82 ! (invert order of indices because "p3d" is in descending order) 82 83 end do 83 84 84 85 ! Other latitudes: 85 do j = 2, jjm86 do i = 1, iim87 o3_mob_regr(i, j, llm:1:-1) &86 do j = 2, nbp_lat-1 87 do i = 1, nbp_lon 88 o3_mob_regr(i, j, klev:1:-1) & 88 89 = regr1_step_av(r_mob(j, :), press_in_edg, & 89 p3d(i, j, llm+1:1:-1))90 p3d(i, j, klev+1:1:-1)) 90 91 ! (invert order of indices because "p3d" is in descending order) 91 92 end do … … 93 94 94 95 ! Duplicate pole values on all longitudes: 95 o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies= iim)96 o3_mob_regr(2:, jjm + 1, :) &97 = spread(o3_mob_regr(1, jjm + 1, :), dim=1, ncopies=iim)96 o3_mob_regr(2:, 1, :) = spread(o3_mob_regr(1, 1, :), dim=1, ncopies=nbp_lon) 97 o3_mob_regr(2:, nbp_lat, :) & 98 = spread(o3_mob_regr(1, nbp_lat, :), dim=1, ncopies=nbp_lon) 98 99 99 100 ! Duplicate first longitude to last longitude: 100 o3_mob_regr( iim + 1, 2:jjm, :) = o3_mob_regr(1, 2:jjm, :)101 o3_mob_regr(nbp_lon + 1, 2:nbp_lat-1, :) = o3_mob_regr(1, 2:nbp_lat-1, :) 101 102 102 103 end subroutine regr_pr_o3 -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/thermcell_old.F90
r3818 r3819 327 327 ! print*,k,lmax(1,k) 328 328 END DO 329 ! print*,'ZMAX ZMAX ZMAX ',zmax330 ! call dump2d(iim,jjm-1,zmax(2:ngrid-1),'ZMAX ')331 329 332 330 ! print*,'OKl336' -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_bilKP_ave.h
r3809 r3819 11 11 itau_w = itau_phy + itap + start_time * day_step / iphysiq 12 12 c 13 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ue_lay,zx_tmp_3d)14 13 CALL histwrite_phy(nid_bilKPave,"ue",itau_w,ue_lay) 15 14 c 16 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ve_lay,zx_tmp_3d)17 15 CALL histwrite_phy(nid_bilKPave,"ve",itau_w,ve_lay) 18 16 c 19 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, uq_lay,zx_tmp_3d)20 17 CALL histwrite_phy(nid_bilKPave,"uq",itau_w,uq_lay) 21 18 c 22 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, vq_lay,zx_tmp_3d)23 19 CALL histwrite_phy(nid_bilKPave,"vq",itau_w,vq_lay) 24 20 c 25 21 c Champs 3D: 26 22 C 27 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, t_seri, zx_tmp_3d)28 23 CALL histwrite_phy(nid_bilKPave,"temp",itau_w,t_seri) 29 24 c 30 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, qx(1,1,ivap), zx_tmp_3d)31 25 CALL histwrite_phy(nid_bilKPave,"ovap",itau_w,qx(:,:,ivap)) 32 26 c 33 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, zphi, zx_tmp_3d)34 27 CALL histwrite_phy(nid_bilKPave,"geop",itau_w,zphi) 35 28 c 36 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, u_seri, zx_tmp_3d)37 29 CALL histwrite_phy(nid_bilKPave,"vitu",itau_w,u_seri) 38 30 c 39 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, v_seri, zx_tmp_3d)40 31 CALL histwrite_phy(nid_bilKPave,"vitv",itau_w,v_seri) 41 32 c 42 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, omega, zx_tmp_3d)43 33 CALL histwrite_phy(nid_bilKPave,"vitw",itau_w,omega) 44 34 c 45 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, pplay, zx_tmp_3d)46 35 CALL histwrite_phy(nid_bilKPave,"pres",itau_w,pplay) 47 36 c 48 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, paprs, zx_tmp_3d)49 37 CALL histwrite_phy(nid_bilKPave,"play",itau_w,paprs) 50 38 c 51 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cldliq, zx_tmp_3d)52 39 CALL histwrite_phy(nid_bilKPave,"oliq",itau_w,cldliq) 53 40 c 54 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_dyn, zx_tmp_3d)55 41 CALL histwrite_phy(nid_bilKPave,"dtdyn",itau_w,d_t_dyn) 56 42 c 57 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_dyn, zx_tmp_3d)58 43 CALL histwrite_phy(nid_bilKPave,"dqdyn",itau_w,d_q_dyn) 59 44 c 60 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_con, zx_tmp_3d)61 45 CALL histwrite_phy(nid_bilKPave,"dtcon",itau_w,d_t_con) 62 46 c 63 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_con, zx_tmp_3d)64 47 CALL histwrite_phy(nid_bilKPave,"ducon",itau_w,d_u_con) 65 48 c 66 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_con, zx_tmp_3d)67 49 CALL histwrite_phy(nid_bilKPave,"dvcon",itau_w,d_v_con) 68 50 c 69 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_con, zx_tmp_3d)70 51 CALL histwrite_phy(nid_bilKPave,"dqcon",itau_w,d_q_con) 71 52 c 72 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_lsc, zx_tmp_3d)73 53 CALL histwrite_phy(nid_bilKPave,"dtlsc",itau_w,d_t_lsc) 74 54 c 75 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_lsc, zx_tmp_3d)76 55 CALL histwrite_phy(nid_bilKPave,"dqlsc",itau_w,d_q_lsc) 77 56 c 78 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_vdf, zx_tmp_3d)79 57 CALL histwrite_phy(nid_bilKPave,"dtvdf",itau_w,d_t_vdf) 80 58 c 81 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_vdf, zx_tmp_3d)82 59 CALL histwrite_phy(nid_bilKPave,"dqvdf",itau_w,d_q_vdf) 83 60 c 84 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_ajs, zx_tmp_3d)85 61 CALL histwrite_phy(nid_bilKPave,"dtajs",itau_w,d_t_ajs) 86 62 c 87 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_ajs, zx_tmp_3d)88 63 CALL histwrite_phy(nid_bilKPave,"dqajs",itau_w,d_q_ajs) 89 64 c 90 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_eva, zx_tmp_3d)91 65 CALL histwrite_phy(nid_bilKPave,"dteva",itau_w,d_t_eva) 92 66 c 93 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_eva, zx_tmp_3d)94 67 CALL histwrite_phy(nid_bilKPave,"dqeva",itau_w,d_q_eva) 95 68 c 96 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat, zx_tmp_3d)97 69 CALL histwrite_phy(nid_bilKPave,"dtswr",itau_w,heat) 98 70 c 99 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat0, zx_tmp_3d)100 71 CALL histwrite_phy(nid_bilKPave,"dtsw0",itau_w,heat0) 101 72 c 102 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool, zx_tmp_3d)103 73 CALL histwrite_phy(nid_bilKPave,"dtlwr",itau_w,cool) 104 74 c 105 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool0, zx_tmp_3d)106 75 CALL histwrite_phy(nid_bilKPave,"dtlw0",itau_w,cool0) 107 76 c 108 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_vdf, zx_tmp_3d)109 77 CALL histwrite_phy(nid_bilKPave,"duvdf",itau_w,d_u_vdf) 110 78 c 111 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_vdf, zx_tmp_3d)112 79 CALL histwrite_phy(nid_bilKPave,"dvvdf",itau_w,d_v_vdf) 113 80 c … … 122 89 ENDDO 123 90 c 124 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_oli, zx_tmp_3d)125 91 CALL histwrite_phy(nid_bilKPave,"duoli",d_u_oli) 126 92 c 127 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_oli, zx_tmp_3d)128 93 CALL histwrite_phy(nid_bilKPave,"dvoli",itau_w,d_v_oli) 129 94 c … … 131 96 ENDIF 132 97 C 133 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u, zx_tmp_3d)134 98 CALL histwrite_phy(nid_bilKPave,"duphy",itau_w,d_u) 135 99 c 136 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v, zx_tmp_3d)137 100 CALL histwrite_phy(nid_bilKPave,"dvphy",itau_w,d_v) 138 101 c 139 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t, zx_tmp_3d)140 102 CALL histwrite_phy(nid_bilKPave,"dtphy",itau_w,d_t) 141 103 c 142 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,1),143 cymf .zx_tmp_3d)144 104 CALL histwrite_phy(nid_bilKPave,"dqphy",itau_w,d_qx(:,:,1)) 145 105 c 146 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,2),147 cym .zx_tmp_3d)148 106 CALL histwrite_phy(nid_bilKPave,"dqlphy",itau_w,d_qx(:,:,2)) 149 107 c -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_bilKP_ins.h
r3809 r3819 11 11 c Champs 3D: 12 12 c 13 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ue_lay,zx_tmp_3d)14 13 CALL histwrite_phy(nid_bilKPins,"ue",itau_w,ue_lay) 15 14 c 16 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, ve_lay,zx_tmp_3d)17 15 CALL histwrite_phy(nid_bilKPins,"ve",itau_w,ve_lay) 18 16 c 19 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, uq_lay,zx_tmp_3d)20 17 CALL histwrite_phy(nid_bilKPins,"uq",itau_w,uq_lay) 21 18 c 22 cym CALL gr_fi_ecrit(klev, klon,iim,jjmp1, vq_lay,zx_tmp_3d)23 19 CALL histwrite_phy(nid_bilKPins,"vq",itau_w,vq_lay) 24 20 c 25 21 c Champs 3D: 26 22 C 27 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, t_seri, zx_tmp_3d)28 23 CALL histwrite_phy(nid_bilKPins,"temp",itau_w,t_seri) 29 24 c 30 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, qx(1,1,ivap), zx_tmp_3d)31 25 CALL histwrite_phy(nid_bilKPins,"ovap",itau_w,qx(:,:,ivap)) 32 26 c 33 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, zphi, zx_tmp_3d)34 27 CALL histwrite_phy(nid_bilKPins,"geop",itau_w,zphi) 35 28 c 36 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, u_seri, zx_tmp_3d)37 29 CALL histwrite_phy(nid_bilKPins,"vitu",itau_w,u_seri) 38 30 c 39 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, v_seri, zx_tmp_3d)40 31 CALL histwrite_phy(nid_bilKPins,"vitv",itau_w,v_seri) 41 32 c 42 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, omega, zx_tmp_3d)43 33 CALL histwrite_phy(nid_bilKPins,"vitw",itau_w,omega) 44 34 c 45 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, pplay, zx_tmp_3d)46 35 CALL histwrite_phy(nid_bilKPins,"pres",itau_w,pplay) 47 36 c 48 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, paprs, zx_tmp_3d)49 37 CALL histwrite_phy(nid_bilKPins,"play",itau_w,paprs) 50 38 c 51 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cldliq, zx_tmp_3d)52 39 CALL histwrite_phy(nid_bilKPins,"oliq",itau_w,cldliq) 53 40 c 54 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_dyn, zx_tmp_3d)55 41 CALL histwrite_phy(nid_bilKPins,"dtdyn",itau_w,d_t_dyn) 56 42 c 57 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_dyn, zx_tmp_3d)58 43 CALL histwrite_phy(nid_bilKPins,"dqdyn",itau_w,d_q_dyn) 59 44 c 60 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_con, zx_tmp_3d)61 45 CALL histwrite_phy(nid_bilKPins,"dtcon",itau_w,d_t_con) 62 46 c 63 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_con, zx_tmp_3d)64 47 CALL histwrite_phy(nid_bilKPins,"ducon",itau_w,d_u_con) 65 c 66 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_con, zx_tmp_3d) 48 c => toi-même ! 49 67 50 CALL histwrite_phy(nid_bilKPins,"dvcon",itau_w,d_v_con) 68 51 c 69 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_con, zx_tmp_3d)70 52 CALL histwrite_phy(nid_bilKPins,"dqcon",itau_w,d_q_con) 71 53 c 72 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_lsc, zx_tmp_3d)73 54 CALL histwrite_phy(nid_bilKPins,"dtlsc",itau_w,d_t_lsc) 74 55 c 75 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_lsc, zx_tmp_3d)76 56 CALL histwrite_phy(nid_bilKPins,"dqlsc",itau_w,d_q_lsc) 77 57 c 78 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_vdf, zx_tmp_3d)79 58 CALL histwrite_phy(nid_bilKPins,"dtvdf",itau_w,d_t_vdf) 80 59 c 81 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_vdf, zx_tmp_3d)82 60 CALL histwrite_phy(nid_bilKPins,"dqvdf",itau_w,d_q_vdf) 83 61 c 84 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_ajs, zx_tmp_3d)85 62 CALL histwrite_phy(nid_bilKPins,"dtajs",itau_w,d_t_ajs) 86 63 c 87 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_ajs, zx_tmp_3d)88 64 CALL histwrite_phy(nid_bilKPins,"dqajs",itau_w,d_q_ajs) 89 65 c 90 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t_eva, zx_tmp_3d)91 66 CALL histwrite_phy(nid_bilKPins,"dteva",itau_w,d_t_eva) 92 67 c 93 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_q_eva, zx_tmp_3d)94 68 CALL histwrite_phy(nid_bilKPins,"dqeva",itau_w,d_q_eva) 95 69 c 96 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat, zx_tmp_3d)97 70 CALL histwrite_phy(nid_bilKPins,"dtswr",itau_w,heat) 98 71 c 99 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, heat0, zx_tmp_3d)100 72 CALL histwrite_phy(nid_bilKPins,"dtsw0",itau_w,heat0) 101 73 c 102 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool, zx_tmp_3d)103 74 CALL histwrite_phy(nid_bilKPins,"dtlwr",itau_w,cool) 104 75 c 105 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, cool0, zx_tmp_3d)106 76 CALL histwrite_phy(nid_bilKPins,"dtlw0",itau_w,cool0) 107 77 c 108 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_vdf, zx_tmp_3d)109 78 CALL histwrite_phy(nid_bilKPins,"duvdf",itau_w,d_u_vdf) 110 79 c 111 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_vdf, zx_tmp_3d)112 80 CALL histwrite_phy(nid_bilKPins,"dvvdf",itau_w,d_v_vdf) 113 81 c … … 122 90 ENDDO 123 91 c 124 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u_oli, zx_tmp_3d)125 92 CALL histwrite_phy(nid_bilKPins,"duoli",itau_w,d_u_oli) 126 93 c 127 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v_oli, zx_tmp_3d)128 94 CALL histwrite_phy(nid_bilKPins,"dvoli",itau_w,d_v_oli) 129 95 c … … 131 97 ENDIF 132 98 C 133 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_u, zx_tmp_3d)134 99 CALL histwrite_phy(nid_bilKPins,"duphy",itau_w,d_u) 135 100 c 136 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_v, zx_tmp_3d)137 101 CALL histwrite_phy(nid_bilKPins,"dvphy",itau_w,d_v) 138 102 c 139 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_t, zx_tmp_3d)140 103 CALL histwrite_phy(nid_bilKPins,"dtphy",itau_w,d_t) 141 104 c 142 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,1),143 cym .zx_tmp_3d)144 105 CALL histwrite_phy(nid_bilKPins,"dqphy",itau_w,d_qx(:,:,1)) 145 106 c 146 cym CALL gr_fi_ecrit(klev,klon,iim,jjmp1, d_qx(:,:,2),147 cym .zx_tmp_3d)148 107 CALL histwrite_phy(nid_bilKPins,"dqlphy",itau_w,d_qx(:,:,2)) 149 108 c … … 161 120 IF(bb2.EQ."850") THEN 162 121 c 163 cym CALL gr_fi_ecrit(1, klon,iim,jjmp1,usumSTD(:,k,1),zx_tmp_2d)164 122 CALL histwrite_phy(nid_bilKPins,"u"//bb2,itau_w,usumSTD(:,k,1)) 165 123 c 166 cym CALL gr_fi_ecrit(1, klon,iim,jjmp1,vsumSTD(:,k,1),zx_tmp_2d)167 124 CALL histwrite_phy(nid_bilKPins,"v"//bb2,itau_w,vsumSTD(:,k,1)) 168 125 c -
dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/write_histday_seri.h
r3818 r3819 24 24 zx_tmp_fi2d(1:klon)=moyglo 25 25 ! 26 CALL gr _fi_ecrit(1, klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)26 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 27 27 CALL histwrite(nid_day_seri,"bilTOA",itau_w, & 28 28 zx_tmp_2d,nbp_lon*jjmp1,ndex2d) … … 33 33 zx_tmp_fi2d(1:klon)=moyglo 34 34 ! 35 CALL gr _fi_ecrit(1, klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)35 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 36 36 CALL histwrite(nid_day_seri,"bils",itau_w, & 37 37 zx_tmp_2d,nbp_lon*jjmp1,ndex2d) … … 48 48 zx_tmp_fi2d(1:klon)=moyglo 49 49 ! 50 CALL gr _fi_ecrit(1, klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)50 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 51 51 CALL histwrite(nid_day_seri,"ecin",itau_w, & 52 52 zx_tmp_2d,nbp_lon*jjmp1,ndex2d) … … 129 129 !#endif 130 130 131 CALL gr _fi_ecrit(1,klon,nbp_lon,jjmp1,airephy,zx_tmp_2d)131 CALL grid1dTo2d_glo(airephy,zx_tmp_2d) 132 132 airetot=0. 133 133 ! DO j = 1, jjmp1 … … 160 160 ! 161 161 zx_tmp_fi2d(1:klon)=aam/airetot 162 CALL gr _fi_ecrit(1,klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)162 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 163 163 CALL histwrite(nid_day_seri,"momang",itau_w,zx_tmp_2d, & 164 164 nbp_lon*jjmp1,ndex2d) 165 165 ! 166 166 zx_tmp_fi2d(1:klon)=torsfc/airetot 167 CALL gr _fi_ecrit(1,klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)167 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 168 168 CALL histwrite(nid_day_seri,"torsfc",itau_w,zx_tmp_2d, & 169 169 nbp_lon*jjmp1,ndex2d) … … 175 175 zx_tmp_fi2d(1:klon)=moyglo 176 176 ! 177 CALL gr _fi_ecrit(1,klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)177 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 178 178 CALL histwrite(nid_day_seri,"tamv",itau_w, & 179 179 zx_tmp_2d,nbp_lon*jjmp1,ndex2d) … … 184 184 zx_tmp_fi2d(1:klon)=moyglo 185 185 ! 186 CALL gr _fi_ecrit(1, klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)186 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 187 187 CALL histwrite(nid_day_seri,"psol",itau_w, & 188 188 zx_tmp_2d,nbp_lon*jjmp1,ndex2d) … … 193 193 zx_tmp_fi2d(1:klon)=moyglo 194 194 ! 195 CALL gr _fi_ecrit(1, klon,nbp_lon,jjmp1,zx_tmp_fi2d,zx_tmp_2d)195 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 196 196 CALL histwrite(nid_day_seri,"evap",itau_w, & 197 197 zx_tmp_2d,nbp_lon*jjmp1,ndex2d) … … 237 237 zx_tmp_fi2d(1:klon)=moyglo 238 238 ! 239 CALL gr _fi_ecrit(1, klon,nbp_lon,jjmp1, zx_tmp_fi2d,zx_tmp_2d)239 CALL grid1dTo2d_glo(zx_tmp_fi2d,zx_tmp_2d) 240 240 CALL histwrite(nid_day_seri,"tsol_"//clnsurf(is_oce), & 241 241 itau_w,zx_tmp_2d,nbp_lon*jjmp1,ndex2d)
Note: See TracChangeset
for help on using the changeset viewer.