Changeset 492 for trunk/LMDZ.COMMON/libf/dyn3dpar
- Timestamp:
- Jan 5, 2012, 8:28:41 AM (13 years ago)
- Location:
- trunk/LMDZ.COMMON/libf/dyn3dpar
- Files:
-
- 13 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.COMMON/libf/dyn3dpar/ce0l.F90
r270 r492 1 1 ! 2 ! $Id: ce0l.F90 1 511 2011-04-28 15:21:47Z jghattas $2 ! $Id: ce0l.F90 1600 2011-12-06 13:16:30Z jghattas $ 3 3 ! 4 4 !------------------------------------------------------------------------------- … … 19 19 USE dimphy 20 20 USE comgeomphy 21 USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root 22 USE mod_const_mpi 21 23 USE infotrac 24 USE parallel, ONLY: finalize_parallel 22 25 23 26 #ifdef CPP_IOIPSL … … 28 31 IMPLICIT NONE 29 32 #ifndef CPP_EARTH 30 WRITE( lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'33 WRITE(*,*)'limit_netcdf: Earth-specific routine, needs Earth physics' 31 34 #else 32 35 !------------------------------------------------------------------------------- … … 39 42 #include "temps.h" 40 43 #include "logic.h" 44 #ifdef CPP_MPI 45 include 'mpif.h' 46 #endif 47 41 48 INTEGER, PARAMETER :: longcles=20 49 INTEGER :: ierr 42 50 REAL, DIMENSION(longcles) :: clesphy0 43 51 REAL, DIMENSION(iip1,jjp1) :: masque … … 47 55 CALL conf_gcm( 99, .TRUE. , clesphy0 ) 48 56 57 #ifdef CPP_MPI 58 CALL init_mpi 59 #endif 60 49 61 CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/)) 50 62 WRITE(lunout,*)'---> klon=',klon 63 IF (mpi_size>1 .OR. omp_size>1) THEN 64 CALL abort_gcm('ce0l','In parallel mode, & 65 & ce0l must be called only & 66 & for 1 process and 1 task',1) 67 ENDIF 68 51 69 CALL InitComgeomphy 52 70 … … 67 85 #endif 68 86 69 IF ( config_inca /= 'none') THEN87 IF (type_trac == 'inca') THEN 70 88 #ifdef INCA 71 CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday) 72 CALL init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0) 73 WRITE(lunout,*)'nbtr =' , nbtr 89 CALL init_const_lmdz( & 90 nbtr,anneeref,dayref,& 91 iphysiq,day_step,nday,& 92 nbsrf, is_oce,is_sic,& 93 is_ter,is_lic) 94 74 95 #endif 75 96 END IF … … 100 121 CALL grilles_gcm_netcdf_sub(masque,phis) 101 122 END IF 123 124 #ifdef CPP_MPI 125 !$OMP MASTER 126 CALL MPI_FINALIZE(ierr) 127 IF (ierr /= 0) CALL abort_gcm('ce0l','Error in MPI_FINALIZE',1) 128 !$OMP END MASTER 129 #endif 130 102 131 #endif 103 132 ! of #ifndef CPP_EARTH #else -
trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F
r271 r492 17 17 use parallel, ONLY : omp_chunk 18 18 USE control_mod 19 USE infotrac, ONLY : type_trac 19 20 IMPLICIT NONE 20 21 c----------------------------------------------------------------------- … … 97 98 CALL getin('lunout', lunout) 98 99 IF (lunout /= 5 .and. lunout /= 6) THEN 99 OPEN(lunout,FILE='lmdz.out') 100 OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write', 101 & STATUS='unknown',FORM='formatted') 102 100 103 ENDIF 101 104 … … 166 169 nday = 10 167 170 CALL getin('nday',nday) 171 172 !Config Key = starttime 173 !Config Desc = Heure de depart de la simulation 174 !Config Def = 0 175 !Config Help = Heure de depart de la simulation 176 !Config en jour 177 starttime = 0 178 CALL getin('starttime',starttime) 168 179 169 180 !Config Key = less1day … … 623 634 END IF 624 635 636 !Config Key = type_trac 637 !Config Desc = Choix de couplage avec model de chimie INCA ou REPROBUS 638 !Config Def = lmdz 639 !Config Help = 640 !Config 'lmdz' = pas de couplage, pur LMDZ 641 !Config 'inca' = model de chime INCA 642 !Config 'repr' = model de chime REPROBUS 643 type_trac = 'lmdz' 644 CALL getin('type_trac',type_trac) 645 625 646 !Config Key = config_inca 626 647 !Config Desc = Choix de configuration de INCA … … 699 720 write(lunout,*)' tauyy = ', tauyy 700 721 write(lunout,*)' offline = ', offline 722 write(lunout,*)' type_trac = ', type_trac 701 723 write(lunout,*)' config_inca = ', config_inca 702 724 write(lunout,*)' ok_dynzon = ', ok_dynzon … … 825 847 & 'only the file phystoke.nc will still be created ' 826 848 END IF 849 850 !Config Key = type_trac 851 !Config Desc = Choix de couplage avec model de chimie INCA ou REPROBUS 852 !Config Def = lmdz 853 !Config Help = 854 !Config 'lmdz' = pas de couplage, pur LMDZ 855 !Config 'inca' = model de chime INCA 856 !Config 'repr' = model de chime REPROBUS 857 type_trac = 'lmdz' 858 CALL getin('type_trac',type_trac) 827 859 828 860 !Config Key = config_inca … … 974 1006 write(lunout,*)' tauy = ', tauy 975 1007 write(lunout,*)' offline = ', offline 1008 write(lunout,*)' type_trac = ', type_trac 976 1009 write(lunout,*)' config_inca = ', config_inca 977 1010 write(lunout,*)' ok_dynzon = ', ok_dynzon -
trunk/LMDZ.COMMON/libf/dyn3dpar/control_mod.F90
r270 r492 10 10 IMPLICIT NONE 11 11 12 REAL :: periodav 12 REAL :: periodav, starttime 13 13 INTEGER :: nday,day_step,iperiod,iapp_tracvl,nsplit_phys 14 14 INTEGER :: iconser,iecri,dissip_period,iphysiq,iecrimoy -
trunk/LMDZ.COMMON/libf/dyn3dpar/dynetat0.F
r1 r492 119 119 day_ini = tab_cntrl(30) 120 120 itau_dyn = tab_cntrl(31) 121 start_time = tab_cntrl(32) 121 122 c ................................................................. 122 123 c -
trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem.F
r1 r492 120 120 tab_cntrl(30) = REAL(iday_end) 121 121 tab_cntrl(31) = REAL(itau_dyn + itaufin) 122 c start_time: start_time of simulation (not necessarily 0.) 123 tab_cntrl(32) = start_time 122 124 c 123 125 c ......................................................... … … 136 138 c 137 139 ierr = NF_PUT_ATT_TEXT (nid, NF_GLOBAL, "title", 27, 138 . "Fichier dem marage dynamique")140 . "Fichier demarrage dynamique") 139 141 c 140 142 c Definir les dimensions du fichiers: … … 536 538 #include "iniprint.h" 537 539 538 539 540 INTEGER l 540 541 REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) … … 641 642 #endif 642 643 643 IF ( config_inca /= 'none') THEN644 IF (type_trac == 'inca') THEN 644 645 ! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc 645 646 ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac) … … 654 655 do iq=1,nqtot 655 656 656 IF ( config_inca == 'none') THEN657 IF (type_trac /= 'inca') THEN 657 658 ierr = NF_INQ_VARID(nid, tname(iq), nvarid) 658 659 IF (ierr .NE. NF_NOERR) THEN … … 666 667 ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq)) 667 668 #endif 668 ELSE ! config_inca = 'chem' ou 'aero'669 ELSE ! type_trac = inca 669 670 ! lecture de la valeur du traceur dans start_trac.nc 670 671 IF (ierr_file .ne. 2) THEN … … 730 731 #endif 731 732 ENDIF ! (ierr_file .ne. 2) 732 END IF ! config_inca733 END IF !type_trac 733 734 734 735 ENDDO -
trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem_p.F
r1 r492 1 1 ! 2 ! $Id: dynredem_p.F 1 403 2010-07-01 09:02:53Z fairhead $2 ! $Id: dynredem_p.F 1577 2011-10-20 15:06:47Z fairhead $ 3 3 ! 4 4 c … … 120 120 tab_cntrl(30) = REAL(iday_end) 121 121 tab_cntrl(31) = REAL(itau_dyn + itaufin) 122 c start_time: start_time of simulation (not necessarily 0.) 123 tab_cntrl(32) = start_time 122 124 c 123 125 c ......................................................... … … 650 652 #endif 651 653 652 IF ( config_inca /= 'none') THEN654 IF (type_trac == 'inca') THEN 653 655 ! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc 654 656 inquire(FILE="start_trac.nc", EXIST=exist_file) … … 667 669 do iq=1,nqtot 668 670 669 IF ( config_inca == 'none') THEN671 IF (type_trac /= 'inca') THEN 670 672 ierr = NF_INQ_VARID(nid, tname(iq), nvarid) 671 673 IF (ierr .NE. NF_NOERR) THEN … … 678 680 ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq)) 679 681 #endif 680 ELSE ! config_inca = 'chem' ou 'aero'682 ELSE ! type_trac = inca 681 683 ! lecture de la valeur du traceur dans start_trac.nc 682 684 IF (ierr_file .ne. 2) THEN … … 732 734 #endif 733 735 ENDIF ! (ierr_file .ne. 2) 734 END IF ! config_inca736 END IF ! type_trac 735 737 736 738 ENDDO -
trunk/LMDZ.COMMON/libf/dyn3dpar/filtreg_p.F
r1 r492 208 208 IF( ifiltre.EQ.-2 ) THEN 209 209 DO j = jdfil,jffil 210 #ifdef BLAS 210 211 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 211 212 & matrinvn(1,1,j), iim, 212 213 & champ_loc(1,j,1), iip1*nlat, 0.0, 213 214 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 215 #else 216 champ_fft(:,j-jdfil+1,:) 217 & =matmul(matrinvn(:,:,j),champ_loc(:iim,j,:)) 218 #endif 214 219 ENDDO 215 220 216 221 ELSE IF ( griscal ) THEN 217 222 DO j = jdfil,jffil 223 #ifdef BLAS 218 224 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 219 225 & matriceun(1,1,j), iim, 220 226 & champ_loc(1,j,1), iip1*nlat, 0.0, 221 227 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 228 #else 229 champ_fft(:,j-jdfil+1,:) 230 & =matmul(matriceun(:,:,j),champ_loc(:iim,j,:)) 231 #endif 222 232 ENDDO 223 233 224 234 ELSE 225 235 DO j = jdfil,jffil 236 #ifdef BLAS 226 237 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 227 238 & matricevn(1,1,j), iim, 228 239 & champ_loc(1,j,1), iip1*nlat, 0.0, 229 240 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 241 #else 242 champ_fft(:,j-jdfil+1,:) 243 & =matmul(matricevn(:,:,j),champ_loc(:iim,j,:)) 244 #endif 230 245 ENDDO 231 246 … … 236 251 IF( ifiltre.EQ.-2 ) THEN 237 252 DO j = jdfil,jffil 253 #ifdef BLAS 238 254 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 239 255 & matrinvs(1,1,j-jfiltsu+1), iim, 240 256 & champ_loc(1,j,1), iip1*nlat, 0.0, 241 257 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 258 #else 259 champ_fft(:,j-jdfil+1,:) 260 & =matmul(matrinvs(:,:,j-jfiltsu+1), 261 & champ_loc(:iim,j,:)) 262 #endif 242 263 ENDDO 243 264 … … 245 266 246 267 DO j = jdfil,jffil 268 #ifdef BLAS 247 269 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 248 270 & matriceus(1,1,j-jfiltsu+1), iim, 249 271 & champ_loc(1,j,1), iip1*nlat, 0.0, 250 272 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 273 #else 274 champ_fft(:,j-jdfil+1,:) 275 & =matmul(matriceus(:,:,j-jfiltsu+1), 276 & champ_loc(:iim,j,:)) 277 #endif 251 278 ENDDO 252 279 … … 254 281 255 282 DO j = jdfil,jffil 283 #ifdef BLAS 256 284 CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0, 257 285 & matricevs(1,1,j-jfiltsv+1), iim, 258 286 & champ_loc(1,j,1), iip1*nlat, 0.0, 259 287 & champ_fft(1,j-jdfil+1,1), iip1*nlat) 288 #else 289 champ_fft(:,j-jdfil+1,:) 290 & =matmul(matricevs(:,:,j-jfiltsv+1), 291 & champ_loc(:iim,j,:)) 292 #endif 260 293 ENDDO 261 294 -
trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F
r130 r492 250 250 c----------------------------------------------------------------------- 251 251 252 IF ( config_inca /= 'none') THEN252 IF (type_trac == 'inca') THEN 253 253 #ifdef INCA 254 254 call init_const_lmdz( … … 337 337 C on remet le calendrier à zero si demande 338 338 c 339 IF (start_time /= starttime) then 340 WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le' 341 &,' fichier restart ne correspond pas à celle lue dans le run.def' 342 IF (raz_date == 1) then 343 WRITE(lunout,*)'Je prends l''heure lue dans run.def' 344 start_time = starttime 345 ELSE 346 WRITE(lunout,*)'Je m''arrete' 347 CALL abort 348 ENDIF 349 ENDIF 339 350 IF (raz_date == 1) THEN 340 351 annee_ref = anneeref … … 480 491 c Initialisation des dimensions d'INCA : 481 492 c -------------------------------------- 482 IF ( config_inca /= 'none') THEN493 IF (type_trac == 'inca') THEN 483 494 #ifdef INCA 484 495 !$OMP PARALLEL -
trunk/LMDZ.COMMON/libf/dyn3dpar/infotrac.F90
r66 r492 32 32 SUBROUTINE infotrac_init 33 33 USE control_mod 34 #ifdef REPROBUS 35 USE CHEM_REP, ONLY : Init_chem_rep_trac 36 #endif 34 37 IMPLICIT NONE 35 38 !======================================================================= … … 85 88 86 89 IF (planet_type=='earth') THEN 87 IF (config_inca=='none') THEN 88 type_trac='lmdz' 90 ! Coherence test between parameter type_trac, config_inca and preprocessing keys 91 IF (type_trac=='inca') THEN 92 WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', & 93 type_trac,' config_inca=',config_inca 94 IF (config_inca/='aero' .AND. config_inca/='chem') THEN 95 WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def' 96 CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1) 97 END IF 98 #ifndef INCA 99 WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code' 100 CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1) 101 #endif 102 ELSE IF (type_trac=='repr') THEN 103 WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac 104 #ifndef REPROBUS 105 WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code' 106 CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1) 107 #endif 108 ELSE IF (type_trac == 'lmdz') THEN 109 WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac 89 110 ELSE 90 type_trac='inca' 111 WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops' 112 CALL abort_gcm('infotrac_init','bad parameter',1) 113 END IF 114 115 ! Test if config_inca is other then none for run without INCA 116 IF (type_trac/='inca' .AND. config_inca/='none') THEN 117 WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model' 118 config_inca='none' 91 119 END IF 92 120 ELSE 93 121 type_trac='plnt' ! planets... May want to dissociate between each later. 94 ENDIF 122 ENDIF ! of IF (planet_type=='earth') 95 123 96 124 !----------------------------------------------------------------------- … … 101 129 !----------------------------------------------------------------------- 102 130 IF (planet_type=='earth') THEN 103 IF (type_trac == 'lmdz' ) THEN131 IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN 104 132 OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr) 105 133 IF(ierr.EQ.0) THEN 106 WRITE(lunout,*) 'Open traceur.def : ok'134 WRITE(lunout,*) trim(modname),': Open traceur.def : ok' 107 135 READ(90,*) nqtrue 108 136 ELSE 109 WRITE(lunout,*) 'Problem in opening traceur.def'110 WRITE(lunout,*) 'ATTENTIONusing defaut values'137 WRITE(lunout,*) trim(modname),': Problem in opening traceur.def' 138 WRITE(lunout,*) trim(modname),': WARNING using defaut values' 111 139 nqtrue=4 ! Defaut value 112 140 END IF 113 141 ! For Earth, water vapour & liquid tracers are not in the physics 114 142 nbtr=nqtrue-2 115 ELSE 143 ELSE ! type_trac=inca 116 144 ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F 117 145 nqtrue=nbtr+2 … … 121 149 WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum' 122 150 CALL abort_gcm('infotrac_init','Not enough tracers',1) 151 END IF 152 153 ! Transfert number of tracers to Reprobus 154 IF (type_trac == 'repr') THEN 155 #ifdef REPROBUS 156 CALL Init_chem_rep_trac(nbtr) 157 #endif 123 158 END IF 124 159 … … 173 208 !--------------------------------------------------------------------- 174 209 IF (planet_type=='earth') THEN 175 IF (type_trac == 'lmdz' ) THEN210 IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN 176 211 IF(ierr.EQ.0) THEN 177 212 ! Continue to read tracer.def -
trunk/LMDZ.COMMON/libf/dyn3dpar/iniacademic.F90
r270 r492 209 209 ! surface pressure 210 210 if (iflag_phys>2) then 211 ps(:)=108080. ! Earth aqua/terra planets 212 else 211 ! specific value for CMIP5 aqua/terra planets 212 ! "Specify the initial dry mass to be equivalent to 213 ! a global mean surface pressure (101325 minus 245) Pa." 214 ps(:)=101080. 215 else 216 ! use reference surface pressure 213 217 ps(:)=preff 214 218 endif 219 215 220 ! ground geopotential 216 221 phis(:)=0. -
trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F
r270 r492 198 198 199 199 INTEGER :: true_itau 200 LOGICAL :: verbose=.true.201 200 INTEGER :: iapptrac 202 201 INTEGER :: AdjustCount … … 282 281 1 CONTINUE 283 282 284 jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec) 285 jH_cur = jH_ref + & 283 jD_cur = jD_ref + day_ini - day_ref + & 284 & int (itau * dtvr / daysec) 285 jH_cur = jH_ref + start_time + & 286 286 & (itau * dtvr / daysec - int(itau * dtvr / daysec)) 287 if (jH_cur > 1.0 ) then 288 jD_cur = jD_cur +1. 289 jH_cur = jH_cur -1. 290 endif 287 291 288 292 … … 441 445 call allgather_timer_average 442 446 443 if ( Verbose) then447 if (prt_level > 9) then 444 448 445 449 print *,'*********************************' … … 761 765 jD_cur = jD_ref + day_ini - day_ref 762 766 $ + int (itau * dtvr / daysec) 763 jH_cur = jH_ref + 767 jH_cur = jH_ref + start_time + & 764 768 & (itau * dtvr / daysec - int(itau * dtvr / daysec)) 765 769 ! call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes) 770 if (jH_cur > 1.0 ) then 771 jD_cur = jD_cur +1. 772 jH_cur = jH_cur -1. 773 endif 766 774 767 775 c rajout debug -
trunk/LMDZ.COMMON/libf/dyn3dpar/parallel.F90
r66 r492 1 1 ! 2 ! $Id: parallel.F90 1 487 2011-02-11 15:07:54Z jghattas $2 ! $Id: parallel.F90 1575 2011-09-21 13:57:48Z jghattas $ 3 3 ! 4 4 module parallel … … 43 43 integer, dimension(3) :: blocklen,type 44 44 integer :: comp_id 45 45 character(len=4) :: num 46 character(len=20) :: filename 47 46 48 #ifdef CPP_OMP 47 49 INTEGER :: OMP_GET_NUM_THREADS … … 75 77 mpi_rank=0 76 78 ENDIF 77 79 80 81 ! Open text output file with mpi_rank in suffix of file name 82 IF (lunout /= 5 .and. lunout /= 6) THEN 83 WRITE(num,'(I4.4)') mpi_rank 84 filename='lmdz.out_'//num 85 IF (mpi_rank .NE. 0) THEN 86 OPEN(UNIT=lunout,FILE=TRIM(filename),ACTION='write', & 87 STATUS='unknown',FORM='formatted',IOSTAT=ierr) 88 ENDIF 89 ENDIF 90 78 91 79 92 allocate(jj_begin_para(0:mpi_size-1)) -
trunk/LMDZ.COMMON/libf/dyn3dpar/temps.h
r1 r492 14 14 15 15 COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref, & 16 & itau_dyn, itau_phy, jD_ref, jH_ref, calend 16 & itau_dyn, itau_phy, jD_ref, jH_ref, calend, & 17 & start_time 18 17 19 18 20 INTEGER itaufin 19 21 INTEGER itau_dyn, itau_phy 20 22 INTEGER day_ini, day_end, annee_ref, day_ref 21 REAL dt, jD_ref, jH_ref 23 REAL dt, jD_ref, jH_ref, start_time 22 24 CHARACTER (len=10) :: calend 23 25
Note: See TracChangeset
for help on using the changeset viewer.