Changeset 4013 for LMDZ6/branches/Ocean_skin/libf/dyn3dmem
- Timestamp:
- Nov 19, 2021, 4:58:59 PM (3 years ago)
- Location:
- LMDZ6/branches/Ocean_skin
- Files:
-
- 7 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/branches/Ocean_skin
- Property svn:mergeinfo changed
-
LMDZ6/branches/Ocean_skin/libf/dyn3dmem/dynetat0_loc.F90
r3043 r4013 225 225 END SUBROUTINE get_var1 226 226 227 228 227 SUBROUTINE get_var2(var,v) 229 228 CHARACTER(LEN=*), INTENT(IN) :: var 230 229 REAL, INTENT(OUT) :: v(:,:) 231 REAL, ALLOCATABLE :: w4(:,:,:,:) 230 REAL, ALLOCATABLE :: w4(:,:,:,:), w3(:,:,:) 232 231 INTEGER :: nn(4), dids(4), k, nd 232 233 233 234 CALL err(NF90_INQ_VARID(fID,var,vID),"inq",var) 234 ierr=NF90_INQUIRE_VARIABLE(fID,vID,dimids=dids,ndims=nd) 235 ierr=NF90_INQUIRE_VARIABLE(fID,vID,ndims=nd) 236 237 IF(nd==1) THEN 238 CALL err(NF90_GET_VAR(fID,vID,v),"get",var); RETURN 239 END IF 240 ierr=NF90_INQUIRE_VARIABLE(fID,vID,dimids=dids) 241 235 242 DO k=1,nd; ierr=NF90_INQUIRE_DIMENSION(fID,dids(k),len=nn(k)); END DO 236 ALLOCATE(w4(nn(1),nn(2),nn(3),nn(4))) 237 CALL err(NF90_GET_VAR(fID,vID,w4),"get",var) 238 v=RESHAPE(w4,[nn(1)*nn(2),nn(3)]); DEALLOCATE(w4) 243 244 SELECT CASE(nd) 245 CASE(3); ALLOCATE(w3(nn(1),nn(2),nn(3))) 246 CALL err(NF90_GET_VAR(fID,vID,w3),"get",var) 247 v=RESHAPE(w3,[nn(1)*nn(2),nn(3)]); DEALLOCATE(w3) 248 CASE(4); ALLOCATE(w4(nn(1),nn(2),nn(3),nn(4))) 249 CALL err(NF90_GET_VAR(fID,vID,w4),"get",var) 250 v=RESHAPE(w4,[nn(1)*nn(2),nn(3)]); DEALLOCATE(w4) 251 END SELECT 239 252 END SUBROUTINE get_var2 240 253 -
LMDZ6/branches/Ocean_skin/libf/dyn3dmem/dynredem_loc.F90
r3811 r4013 242 242 !$OMP MASTER 243 243 fil="start_trac.nc" 244 IF(type_trac=='inca' ) INQUIRE(FILE=fil,EXIST=lread_inca)244 IF(type_trac=='inca' .OR. type_trac=='inco') INQUIRE(FILE=fil,EXIST=lread_inca) 245 245 IF(lread_inca) CALL err(NF90_OPEN(fil,NF90_NOWRITE,nid_trac),"open") 246 246 !$OMP END MASTER -
LMDZ6/branches/Ocean_skin/libf/dyn3dmem/guide_loc_mod.F90
r3811 r4013 9 9 !======================================================================= 10 10 11 USE getparam 11 USE getparam, only: ini_getparam, fin_getparam, getpar 12 12 USE Write_Field_loc 13 use netcdf, only: nf90_nowrite, nf90_open, nf90_inq_varid, nf90_close 13 use netcdf, only: nf90_nowrite, nf90_open, nf90_inq_varid, nf90_close, & 14 nf90_inq_dimid, nf90_inquire_dimension 14 15 USE parallel_lmdz 15 USE pres2lev_mod 16 USE pres2lev_mod, only: pres2lev 16 17 17 18 IMPLICIT NONE … … 62 63 REAL, ALLOCATABLE, DIMENSION(:), PRIVATE, SAVE :: psgui1,psgui2 63 64 64 INTEGER,SAVE,PRIVATE :: ijbu,ijbv,ijeu,ijev ,ijnu,ijnv65 INTEGER,SAVE,PRIVATE :: ijbu,ijbv,ijeu,ijev !,ijnu,ijnv 65 66 INTEGER,SAVE,PRIVATE :: jjbu,jjbv,jjeu,jjev,jjnu,jjnv 66 67 … … 83 84 CHARACTER (len = 80) :: abort_message 84 85 CHARACTER (len = 20) :: modname = 'guide_init' 86 CHARACTER (len = 20) :: namedim 85 87 86 88 ! --------------------------------------------- … … 173 175 rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl) 174 176 if (rcod.NE.NF_NOERR) THEN 175 print *,'Guide: probleme -> pas de fichierapbp.nc'177 abort_message=' Nudging error -> no file apbp.nc' 176 178 CALL abort_gcm(modname,abort_message,1) 177 179 endif … … 181 183 rcod=nf90_open('P.nc',Nf90_NOWRITe,ncidpl) 182 184 if (rcod.NE.NF_NOERR) THEN 183 print *,'Guide: probleme -> pas de fichierP.nc'185 abort_message=' Nudging error -> no file P.nc' 184 186 CALL abort_gcm(modname,abort_message,1) 185 187 endif 186 188 endif 189 187 190 elseif (guide_u) then 188 191 if (ncidpl.eq.-99) then 189 192 rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl) 190 193 if (rcod.NE.NF_NOERR) THEN 191 print *,'Guide: probleme -> pas de fichieru.nc'194 abort_message=' Nudging error -> no file u.nc' 192 195 CALL abort_gcm(modname,abort_message,1) 193 196 endif 197 194 198 endif 199 200 195 201 elseif (guide_v) then 196 202 if (ncidpl.eq.-99) then 197 203 rcod=nf90_open('v.nc',nf90_nowrite,ncidpl) 198 204 if (rcod.NE.NF_NOERR) THEN 199 print *,'Guide: probleme -> pas de fichierv.nc'205 abort_message=' Nudging error -> no file v.nc' 200 206 CALL abort_gcm(modname,abort_message,1) 201 207 endif 202 208 endif 209 210 203 211 elseif (guide_T) then 204 212 if (ncidpl.eq.-99) then 205 213 rcod=nf90_open('T.nc',nf90_nowrite,ncidpl) 206 214 if (rcod.NE.NF_NOERR) THEN 207 print *,'Guide: probleme -> pas de fichierT.nc'215 abort_message=' Nudging error -> no file T.nc' 208 216 CALL abort_gcm(modname,abort_message,1) 209 217 endif 210 218 endif 219 220 221 211 222 elseif (guide_Q) then 212 223 if (ncidpl.eq.-99) then 213 224 rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl) 214 225 if (rcod.NE.NF_NOERR) THEN 215 print *,'Guide: probleme -> pas de fichierhur.nc'226 abort_message=' Nudging error -> no file hur.nc' 216 227 CALL abort_gcm(modname,abort_message,1) 217 228 endif 218 229 endif 230 231 219 232 endif 220 233 error=NF_INQ_DIMID(ncidpl,'LEVEL',rid) 221 234 IF (error.NE.NF_NOERR) error=NF_INQ_DIMID(ncidpl,'PRESSURE',rid) 222 235 IF (error.NE.NF_NOERR) THEN 223 print *,'Guide: probleme lecture niveaux pression'236 abort_message='Nudging: error reading pressure levels' 224 237 CALL abort_gcm(modname,abort_message,1) 225 238 ENDIF 226 239 error=NF_INQ_DIMLEN(ncidpl,rid,nlevnc) 227 print *,'Guide: nombre niveaux vert. nlevnc', nlevnc240 write(*,*)trim(modname)//' : number of vertical levels nlevnc', nlevnc 228 241 rcod = nf90_close(ncidpl) 229 242 … … 231 244 ! Allocation des variables 232 245 ! --------------------------------------------- 233 abort_message=' pb in allocation guide'246 abort_message='nudging allocation error' 234 247 235 248 ALLOCATE(apnc(nlevnc), stat = error) … … 382 395 383 396 INTEGER :: i,j,l 384 INTEGER,EXTERNAL :: OMP_GET_THREAD_NUM397 CHARACTER(LEN=20) :: modname="guide_main" 385 398 386 399 !$OMP MASTER 387 ijbu=ij_begin ; ijeu=ij_end ; ijnu=ijeu-ijbu+1400 ijbu=ij_begin ; ijeu=ij_end 388 401 jjbu=jj_begin ; jjeu=jj_end ; jjnu=jjeu-jjbu+1 389 ijbv=ij_begin ; ijev=ij_end ; ijnv=ijev-ijbv+1402 ijbv=ij_begin ; ijev=ij_end 390 403 jjbv=jj_begin ; jjev=jj_end ; jjnv=jjev-jjbv+1 391 404 IF (pole_sud) THEN 405 ijeu=ij_end-iip1 392 406 ijev=ij_end-iip1 393 407 jjev=jj_end-1 394 ijnv=ijev-ijbv+1395 408 jjnv=jjev-jjbv+1 409 ENDIF 410 IF (pole_nord) THEN 411 ijbu=ij_begin+iip1 412 ijbv=ij_begin 396 413 ENDIF 397 414 !$OMP END MASTER … … 480 497 IF (reste.EQ.0.) THEN 481 498 IF (itau_test.EQ.itau) THEN 482 write(*,*)'deuxieme passage de advreel a itau=',itau 483 stop 499 write(*,*)trim(modname)//' second pass in advreel at itau=',& 500 itau 501 stop 484 502 ELSE 485 503 !$OMP MASTER … … 494 512 step_rea=step_rea+1 495 513 itau_test=itau 496 print*,'Lecture fichiers guidage, pas ',step_rea, & 497 'apres ',count_no_rea,' non lectures' 514 if (is_master) then 515 write(*,*)trim(modname)//' Reading nudging files, step ',& 516 step_rea,'after ',count_no_rea,' skips' 517 endif 498 518 IF (guide_2D) THEN 499 519 !$OMP MASTER … … 534 554 535 555 536 556 !----------------------------------------------------------------------- 537 557 ! Ajout des champs de guidage 538 558 !----------------------------------------------------------------------- … … 563 583 ENDDO 564 584 565 !!$OMP MASTER566 ! DO l=1,llm,5567 ! print*,'avant dump2d l=',l,mpi_rank,OMP_GET_THREAD_NUM()568 ! print*,'avant dump2d l=',l,mpi_rank569 ! CALL dump2d(iip1,jjnb_u,p(:,l),'ppp ')570 ! ENDDO571 !!$OMP END MASTER572 !!$OMP BARRIER573 574 585 CALL guide_out("SP",jjp1,llm,p(ijb_u:ije_u,1:llm),1.) 575 586 ENDIF … … 592 603 if (guide_zon) CALL guide_zonave_u(1,llm,f_addu) 593 604 CALL guide_addfield_u(llm,f_addu,alpha_u) 594 ! IF (f_out) CALL guide_out("ua",jjp1,llm,ugui1(ijb_u:ije_u,:),factt)595 605 IF (f_out) CALL guide_out("ua",jjp1,llm,(1.-tau)*ugui1(ijb_u:ije_u,:)+tau*ugui2(ijb_u:ije_u,:),factt) 596 606 IF (f_out) CALL guide_out("u",jjp1,llm,ucov(ijb_u:ije_u,:),factt) 597 IF (f_out) CALL guide_out("ucov",jjp1,llm,f_addu(ijb_u:ije_u,:),factt) 607 IF (f_out) THEN 608 ! Ehouarn: fill the gaps adequately... 609 IF (ijbu>ijb_u) f_addu(ijb_u:ijbu-1,:)=0 610 IF (ijeu<ije_u) f_addu(ijeu+1:ije_u,:)=0 611 CALL guide_out("ucov",jjp1,llm,f_addu(ijb_u:ije_u,:)/factt,factt) 612 ENDIF 598 613 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) 599 614 DO l=1,llm … … 690 705 IF (f_out) CALL guide_out("v",jjm,llm,vcov(ijb_v:ije_v,:),factt) 691 706 IF (f_out) CALL guide_out("va",jjm,llm,(1.-tau)*vgui1(ijb_v:ije_v,:)+tau*vgui2(ijb_v:ije_v,:),factt) 692 IF (f_out) CALL guide_out("vcov",jjm,llm,f_addv(:,:)/factt,factt) 707 IF (f_out) THEN 708 ! Ehouarn: Fill in the gaps adequately 709 IF (ijbv>ijb_v) f_addv(ijb_v:ijbv-1,:)=0 710 IF (ijev<ije_v) f_addv(ijev+1:ije_v,:)=0 711 CALL guide_out("vcov",jjm,llm,f_addv(ijb_v:ije_v,:)/factt,factt) 712 ENDIF 693 713 694 714 !$OMP DO SCHEDULE(STATIC,OMP_CHUNK) … … 926 946 927 947 INTEGER :: i,j,l,ij 948 CHARACTER(LEN=20),PARAMETER :: modname="guide_interp" 928 949 TYPE(Request),SAVE :: Req 929 950 !$OMP THREADPRIVATE(Req) 930 print *,'Guide: conversion variables guidage' 951 952 if (is_master) write(*,*)trim(modname)//': interpolate nudging variables' 931 953 ! ----------------------------------------------------------------- 932 954 ! Calcul des niveaux de pression champs guidage (pour T et Q) … … 973 995 first=.FALSE. 974 996 !$OMP MASTER 975 print*,'Guide: verification ordre niveaux verticaux'976 print*,'LMDZ :'997 write(*,*)trim(modname)//' : check vertical level order' 998 write(*,*)trim(modname)//' LMDZ :' 977 999 do l=1,llm 978 print*,'PL(',l,')=',(ap(l)+ap(l+1))/2. &1000 write(*,*)trim(modname)//' PL(',l,')=',(ap(l)+ap(l+1))/2. & 979 1001 +psi(1,jjeu)*(bp(l)+bp(l+1))/2. 980 1002 enddo 981 print*,'Fichiers guidage'1003 write(*,*)trim(modname)//' nudging file :' 982 1004 SELECT CASE (guide_plevs) 983 1005 CASE (0) 984 1006 do l=1,nlevnc 985 print*,'PL(',l,')=',plnc2(1,jjbu,l)1007 write(*,*)trim(modname)//' PL(',l,')=',plnc2(1,jjbu,l) 986 1008 enddo 987 1009 CASE (1) 988 1010 DO l=1,nlevnc 989 print*,'PL(',l,')=',apnc(l)+bpnc(l)*psnat2(i,jjbu) 990 ENDDO 1011 write(*,*)trim(modname)//' PL(',l,')=',& 1012 apnc(l)+bpnc(l)*psnat2(i,jjbu) 1013 ENDDO 991 1014 CASE (2) 992 1015 do l=1,nlevnc 993 print*,'PL(',l,')=',pnat2(1,jjbu,l)1016 write(*,*)trim(modname)//' PL(',l,')=',pnat2(1,jjbu,l) 994 1017 enddo 995 1018 END SELECT 996 print *,'inversion de l''ordre: invert_p=',invert_p1019 write(*,*)trim(modname)//' invert ordering: invert_p=',invert_p 997 1020 if (guide_u) then 998 1021 do l=1,nlevnc 999 print*,'U(',l,')=',unat2(1,jjbu,l)1022 write(*,*)trim(modname)//' U(',l,')=',unat2(1,jjbu,l) 1000 1023 enddo 1001 1024 endif 1002 1025 if (guide_T) then 1003 1026 do l=1,nlevnc 1004 print*,'T(',l,')=',tnat2(1,jjbu,l)1027 write(*,*)trim(modname)//' T(',l,')=',tnat2(1,jjbu,l) 1005 1028 enddo 1006 1029 endif 1007 1030 !$OMP END MASTER 1008 endif 1031 endif ! of if (first) 1009 1032 1010 1033 ! ----------------------------------------------------------------- … … 1402 1425 real alphamin,alphamax,xi 1403 1426 integer i,j,ilon,ilat 1427 character(len=20),parameter :: modname="tau2alpha" 1404 1428 1405 1429 … … 1490 1514 ! Calcul de gamma 1491 1515 if (abs(grossismx-1.).lt.0.1.or.abs(grossismy-1.).lt.0.1) then 1492 print*,'ATTENTION modele peu zoome'1493 print*,'ATTENTION on prend une constante de guidage cste'1494 1516 write(*,*)trim(modname)//' ATTENTION modele peu zoome' 1517 write(*,*)trim(modname)//' ATTENTION on prend une constante de guidage cste' 1518 gamma=0. 1495 1519 else 1496 1497 print*,'gamma=',gamma1498 1499 print*,'gamma =',gamma,'<1e-5'1500 1501 1502 1503 1504 1505 1506 print*,'gamma=',gamma1520 gamma=(dxdy_max-2.*dxdy_min)/(dxdy_max-dxdy_min) 1521 write(*,*)trim(modname)//' gamma=',gamma 1522 if (gamma.lt.1.e-5) then 1523 write(*,*)trim(modname)//' gamma =',gamma,'<1e-5' 1524 stop 1525 endif 1526 gamma=log(0.5)/log(gamma) 1527 if (gamma4) then 1528 gamma=min(gamma,4.) 1529 endif 1530 write(*,*)trim(modname)//' gamma=',gamma 1507 1531 endif 1508 1532 ENDIF !first … … 1545 1569 IMPLICIT NONE 1546 1570 1547 #include "netcdf.inc"1548 #include "dimensions.h"1549 #include "paramet.h"1571 include "netcdf.inc" 1572 include "dimensions.h" 1573 include "paramet.h" 1550 1574 1551 1575 INTEGER, INTENT(IN) :: timestep … … 1555 1579 INTEGER, SAVE :: ncidu,varidu,ncidv,varidv,ncidp,varidp 1556 1580 INTEGER, SAVE :: ncidQ,varidQ,ncidt,varidt,ncidps,varidps 1557 INTEGER :: ncidpl,varidpl,varidap,varidbp 1581 INTEGER :: ncidpl,varidpl,varidap,varidbp,dimid,lendim 1558 1582 ! Variables auxiliaires NetCDF: 1559 1583 INTEGER, DIMENSION(4) :: start,count … … 1561 1585 CHARACTER (len = 80) :: abort_message 1562 1586 CHARACTER (len = 20) :: modname = 'guide_read' 1587 CHARACTER (len = 20) :: namedim 1563 1588 abort_message='pb in guide_read' 1564 1589 … … 1568 1593 if (first) then 1569 1594 ncidpl=-99 1570 print*,'Guide: ouverture des fichiers guidage'1595 write(*,*),trim(modname)//': opening nudging files ' 1571 1596 ! Ap et Bp si Niveaux de pression hybrides 1572 1597 if (guide_plevs.EQ.1) then 1573 print *,'Lecture du guidage sur niveaux modele'1598 write(*,*),trim(modname)//' Reading nudging on model levels' 1574 1599 rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl) 1575 1600 IF (rcode.NE.NF_NOERR) THEN 1576 print *,'Guide: probleme -> pas de fichierapbp.nc'1601 abort_message='Nudging: error -> no file apbp.nc' 1577 1602 CALL abort_gcm(modname,abort_message,1) 1578 1603 ENDIF 1579 1604 rcode = nf90_inq_varid(ncidpl, 'AP', varidap) 1580 1605 IF (rcode.NE.NF_NOERR) THEN 1581 print *,'Guide: probleme -> pas de variable AP, fichierapbp.nc'1606 abort_message='Nudging: error -> no AP variable in file apbp.nc' 1582 1607 CALL abort_gcm(modname,abort_message,1) 1583 1608 ENDIF 1584 1609 rcode = nf90_inq_varid(ncidpl, 'BP', varidbp) 1585 1610 IF (rcode.NE.NF_NOERR) THEN 1586 print *,'Guide: probleme -> pas de variable BP, fichierapbp.nc'1611 abort_message='Nudging: error -> no BP variable in file apbp.nc' 1587 1612 CALL abort_gcm(modname,abort_message,1) 1588 1613 ENDIF 1589 print*,'ncidpl,varidap',ncidpl,varidap1614 write(*,*),trim(modname)//' ncidpl,varidap',ncidpl,varidap 1590 1615 endif 1616 1591 1617 ! Pression si guidage sur niveaux P variables 1592 1618 if (guide_plevs.EQ.2) then 1593 1619 rcode = nf90_open('P.nc', nf90_nowrite, ncidp) 1594 1620 IF (rcode.NE.NF_NOERR) THEN 1595 print *,'Guide: probleme -> pas de fichierP.nc'1621 abort_message='Nudging: error -> no file P.nc' 1596 1622 CALL abort_gcm(modname,abort_message,1) 1597 1623 ENDIF 1598 1624 rcode = nf90_inq_varid(ncidp, 'PRES', varidp) 1599 1625 IF (rcode.NE.NF_NOERR) THEN 1600 print *,'Guide: probleme -> pas de variable PRES, fichierP.nc'1626 abort_message='Nudging: error -> no PRES variable in file P.nc' 1601 1627 CALL abort_gcm(modname,abort_message,1) 1602 1628 ENDIF 1603 print*,'ncidp,varidp',ncidp,varidp1629 write(*,*),trim(modname)//' ncidp,varidp',ncidp,varidp 1604 1630 if (ncidpl.eq.-99) ncidpl=ncidp 1605 1631 endif 1632 1606 1633 ! Vent zonal 1607 1634 if (guide_u) then 1608 1635 rcode = nf90_open('u.nc', nf90_nowrite, ncidu) 1609 1636 IF (rcode.NE.NF_NOERR) THEN 1610 print *,'Guide: probleme -> pas de fichieru.nc'1637 abort_message='Nudging: error -> no file u.nc' 1611 1638 CALL abort_gcm(modname,abort_message,1) 1612 1639 ENDIF 1613 1640 rcode = nf90_inq_varid(ncidu, 'UWND', varidu) 1614 1641 IF (rcode.NE.NF_NOERR) THEN 1615 print *,'Guide: probleme -> pas de variable UWND, fichieru.nc'1642 abort_message='Nudging: error -> no UWND variable in file u.nc' 1616 1643 CALL abort_gcm(modname,abort_message,1) 1617 1644 ENDIF 1618 print*,'ncidu,varidu',ncidu,varidu1645 write(*,*),trim(modname)//' ncidu,varidu',ncidu,varidu 1619 1646 if (ncidpl.eq.-99) ncidpl=ncidu 1647 1648 1649 status=NF90_INQ_DIMID(ncidu, "LONU", dimid) 1650 status=NF90_INQUIRE_DIMENSION(ncidu,dimid,namedim,lendim) 1651 IF (lendim .NE. iip1) THEN 1652 abort_message='dimension LONU different from iip1 in u.nc' 1653 CALL abort_gcm(modname,abort_message,1) 1654 ENDIF 1655 1656 status=NF90_INQ_DIMID(ncidu, "LATU", dimid) 1657 status=NF90_INQUIRE_DIMENSION(ncidu,dimid,namedim,lendim) 1658 IF (lendim .NE. jjp1) THEN 1659 abort_message='dimension LATU different from jjp1 in u.nc' 1660 CALL abort_gcm(modname,abort_message,1) 1661 ENDIF 1662 1620 1663 endif 1664 1621 1665 ! Vent meridien 1622 1666 if (guide_v) then 1623 1667 rcode = nf90_open('v.nc', nf90_nowrite, ncidv) 1624 1668 IF (rcode.NE.NF_NOERR) THEN 1625 print *,'Guide: probleme -> pas de fichierv.nc'1669 abort_message='Nudging: error -> no file v.nc' 1626 1670 CALL abort_gcm(modname,abort_message,1) 1627 1671 ENDIF 1628 1672 rcode = nf90_inq_varid(ncidv, 'VWND', varidv) 1629 1673 IF (rcode.NE.NF_NOERR) THEN 1630 print *,'Guide: probleme -> pas de variable VWND, fichierv.nc'1674 abort_message='Nudging: error -> no VWND variable in file v.nc' 1631 1675 CALL abort_gcm(modname,abort_message,1) 1632 1676 ENDIF 1633 print*,'ncidv,varidv',ncidv,varidv1677 write(*,*),trim(modname)//' ncidv,varidv',ncidv,varidv 1634 1678 if (ncidpl.eq.-99) ncidpl=ncidv 1635 endif 1679 1680 status=NF90_INQ_DIMID(ncidv, "LONV", dimid) 1681 status=NF90_INQUIRE_DIMENSION(ncidv,dimid,namedim,lendim) 1682 1683 IF (lendim .NE. iip1) THEN 1684 abort_message='dimension LONV different from iip1 in v.nc' 1685 CALL abort_gcm(modname,abort_message,1) 1686 ENDIF 1687 1688 1689 status=NF90_INQ_DIMID(ncidv, "LATV", dimid) 1690 status=NF90_INQUIRE_DIMENSION(ncidv,dimid,namedim,lendim) 1691 IF (lendim .NE. jjm) THEN 1692 abort_message='dimension LATV different from jjm in v.nc' 1693 CALL abort_gcm(modname,abort_message,1) 1694 ENDIF 1695 1696 endif 1697 1636 1698 ! Temperature 1637 1699 if (guide_T) then 1638 1700 rcode = nf90_open('T.nc', nf90_nowrite, ncidt) 1639 1701 IF (rcode.NE.NF_NOERR) THEN 1640 print *,'Guide: probleme -> pas de fichierT.nc'1702 abort_message='Nudging: error -> no file T.nc' 1641 1703 CALL abort_gcm(modname,abort_message,1) 1642 1704 ENDIF 1643 1705 rcode = nf90_inq_varid(ncidt, 'AIR', varidt) 1644 1706 IF (rcode.NE.NF_NOERR) THEN 1645 print *,'Guide: probleme -> pas de variable AIR, fichierT.nc'1707 abort_message='Nudging: error -> no AIR variable in file T.nc' 1646 1708 CALL abort_gcm(modname,abort_message,1) 1647 1709 ENDIF 1648 print*,'ncidT,varidT',ncidt,varidt1710 write(*,*),trim(modname)//' ncidT,varidT',ncidt,varidt 1649 1711 if (ncidpl.eq.-99) ncidpl=ncidt 1712 1713 status=NF90_INQ_DIMID(ncidt, "LONV", dimid) 1714 status=NF90_INQUIRE_DIMENSION(ncidt,dimid,namedim,lendim) 1715 IF (lendim .NE. iip1) THEN 1716 abort_message='dimension LONV different from iip1 in T.nc' 1717 CALL abort_gcm(modname,abort_message,1) 1718 ENDIF 1719 1720 status=NF90_INQ_DIMID(ncidt, "LATU", dimid) 1721 status=NF90_INQUIRE_DIMENSION(ncidt,dimid,namedim,lendim) 1722 IF (lendim .NE. jjp1) THEN 1723 abort_message='dimension LATU different from jjp1 in T.nc' 1724 CALL abort_gcm(modname,abort_message,1) 1725 ENDIF 1726 1650 1727 endif 1728 1651 1729 ! Humidite 1652 1730 if (guide_Q) then 1653 1731 rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ) 1654 1732 IF (rcode.NE.NF_NOERR) THEN 1655 print *,'Guide: probleme -> pas de fichierhur.nc'1733 abort_message='Nudging: error -> no file hur.nc' 1656 1734 CALL abort_gcm(modname,abort_message,1) 1657 1735 ENDIF 1658 1736 rcode = nf90_inq_varid(ncidQ, 'RH', varidQ) 1659 1737 IF (rcode.NE.NF_NOERR) THEN 1660 print *,'Guide: probleme -> pas de variable RH, fichierhur.nc'1738 abort_message='Nudging: error -> no RH variable in file hur.nc' 1661 1739 CALL abort_gcm(modname,abort_message,1) 1662 1740 ENDIF 1663 print*,'ncidQ,varidQ',ncidQ,varidQ1741 write(*,*),trim(modname)//' ncidQ,varidQ',ncidQ,varidQ 1664 1742 if (ncidpl.eq.-99) ncidpl=ncidQ 1743 1744 1745 status=NF90_INQ_DIMID(ncidQ, "LONV", dimid) 1746 status=NF90_INQUIRE_DIMENSION(ncidQ,dimid,namedim,lendim) 1747 IF (lendim .NE. iip1) THEN 1748 abort_message='dimension LONV different from iip1 in hur.nc' 1749 CALL abort_gcm(modname,abort_message,1) 1750 ENDIF 1751 1752 status=NF90_INQ_DIMID(ncidQ, "LATU", dimid) 1753 status=NF90_INQUIRE_DIMENSION(ncidQ,dimid,namedim,lendim) 1754 IF (lendim .NE. jjp1) THEN 1755 abort_message='dimension LATU different from jjp1 in hur.nc' 1756 CALL abort_gcm(modname,abort_message,1) 1757 ENDIF 1758 1759 1665 1760 endif 1666 1761 ! Pression de surface … … 1668 1763 rcode = nf90_open('ps.nc', nf90_nowrite, ncidps) 1669 1764 IF (rcode.NE.NF_NOERR) THEN 1670 print *,'Guide: probleme -> pas de fichierps.nc'1765 abort_message='Nudging: error -> no file ps.nc' 1671 1766 CALL abort_gcm(modname,abort_message,1) 1672 1767 ENDIF 1673 1768 rcode = nf90_inq_varid(ncidps, 'SP', varidps) 1674 1769 IF (rcode.NE.NF_NOERR) THEN 1675 print *,'Guide: probleme -> pas de variable SP, fichierps.nc'1770 abort_message='Nudging: error -> no SP variable in file ps.nc' 1676 1771 CALL abort_gcm(modname,abort_message,1) 1677 1772 ENDIF 1678 print*,'ncidps,varidps',ncidps,varidps1773 write(*,*),trim(modname)//' ncidps,varidps',ncidps,varidps 1679 1774 endif 1680 1775 ! Coordonnee verticale … … 1682 1777 rcode = nf90_inq_varid(ncidpl, 'LEVEL', varidpl) 1683 1778 IF (rcode.NE.0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl) 1684 print*,'ncidpl,varidpl',ncidpl,varidpl1779 write(*,*),trim(modname)//' ncidpl,varidpl',ncidpl,varidpl 1685 1780 endif 1686 1781 ! Coefs ap, bp pour calcul de la pression aux differents niveaux … … 1827 1922 IMPLICIT NONE 1828 1923 1829 #include "netcdf.inc"1830 #include "dimensions.h"1831 #include "paramet.h"1924 include "netcdf.inc" 1925 include "dimensions.h" 1926 include "paramet.h" 1832 1927 1833 1928 INTEGER, INTENT(IN) :: timestep … … 1854 1949 if (first) then 1855 1950 ncidpl=-99 1856 print*,'Guide: ouverture des fichiers guidage'1951 write(*,*)trim(modname)//' : opening nudging files ' 1857 1952 ! Ap et Bp si niveaux de pression hybrides 1858 1953 if (guide_plevs.EQ.1) then 1859 print *,'Lecture du guidage sur niveaux mod�le'1860 1861 1862 print *,'Guide: probleme -> pas de fichierapbp.nc'1863 1864 1865 1866 1867 print *,'Guide: probleme -> pas de variable AP, fichierapbp.nc'1868 1869 1870 1871 1872 print *,'Guide: probleme -> pas de variable BP, fichierapbp.nc'1873 1874 1875 print*,'ncidpl,varidap',ncidpl,varidap1954 write(*,*)trim(modname)//' Reading nudging on model levels' 1955 rcode = nf90_open('apbp.nc', nf90_nowrite, ncidpl) 1956 IF (rcode.NE.NF_NOERR) THEN 1957 abort_message='Nudging: error -> no file apbp.nc' 1958 CALL abort_gcm(modname,abort_message,1) 1959 ENDIF 1960 rcode = nf90_inq_varid(ncidpl, 'AP', varidap) 1961 IF (rcode.NE.NF_NOERR) THEN 1962 abort_message='Nudging: error -> no AP variable in file apbp.nc' 1963 CALL abort_gcm(modname,abort_message,1) 1964 ENDIF 1965 rcode = nf90_inq_varid(ncidpl, 'BP', varidbp) 1966 IF (rcode.NE.NF_NOERR) THEN 1967 abort_message='Nudging: error -> no BP variable in file apbp.nc' 1968 CALL abort_gcm(modname,abort_message,1) 1969 ENDIF 1970 write(*,*)trim(modname)//'ncidpl,varidap',ncidpl,varidap 1876 1971 endif 1877 1972 ! Pression 1878 1973 if (guide_plevs.EQ.2) then 1879 1880 1881 print *,'Guide: probleme -> pas de fichierP.nc'1882 1883 1884 1885 1886 print *,'Guide: probleme -> pas de variable PRES, fichierP.nc'1887 1888 1889 print*,'ncidp,varidp',ncidp,varidp1890 1974 rcode = nf90_open('P.nc', nf90_nowrite, ncidp) 1975 IF (rcode.NE.NF_NOERR) THEN 1976 abort_message='Nudging: error -> no file P.nc' 1977 CALL abort_gcm(modname,abort_message,1) 1978 ENDIF 1979 rcode = nf90_inq_varid(ncidp, 'PRES', varidp) 1980 IF (rcode.NE.NF_NOERR) THEN 1981 abort_message='Nudging: error -> no PRES variable in file P.nc' 1982 CALL abort_gcm(modname,abort_message,1) 1983 ENDIF 1984 write(*,*)trim(modname)//' ncidp,varidp',ncidp,varidp 1985 if (ncidpl.eq.-99) ncidpl=ncidp 1891 1986 endif 1892 1987 ! Vent zonal 1893 1988 if (guide_u) then 1894 1895 1896 print *,'Guide: probleme -> pas de fichieru.nc'1897 1898 1899 1900 1901 print *,'Guide: probleme -> pas de variable UWND, fichieru.nc'1902 1903 1904 print*,'ncidu,varidu',ncidu,varidu1905 1989 rcode = nf90_open('u.nc', nf90_nowrite, ncidu) 1990 IF (rcode.NE.NF_NOERR) THEN 1991 abort_message='Nudging: error -> no file u.nc' 1992 CALL abort_gcm(modname,abort_message,1) 1993 ENDIF 1994 rcode = nf90_inq_varid(ncidu, 'UWND', varidu) 1995 IF (rcode.NE.NF_NOERR) THEN 1996 abort_message='Nudging: error -> no UWND variable in file u.nc' 1997 CALL abort_gcm(modname,abort_message,1) 1998 ENDIF 1999 write(*,*)trim(modname)//' ncidu,varidu',ncidu,varidu 2000 if (ncidpl.eq.-99) ncidpl=ncidu 1906 2001 endif 1907 2002 1908 2003 ! Vent meridien 1909 2004 if (guide_v) then 1910 1911 1912 print *,'Guide: probleme -> pas de fichierv.nc'1913 1914 1915 1916 1917 print *,'Guide: probleme -> pas de variable VWND, fichierv.nc'1918 1919 1920 print*,'ncidv,varidv',ncidv,varidv1921 1922 2005 rcode = nf90_open('v.nc', nf90_nowrite, ncidv) 2006 IF (rcode.NE.NF_NOERR) THEN 2007 abort_message='Nudging: error -> no file v.nc' 2008 CALL abort_gcm(modname,abort_message,1) 2009 ENDIF 2010 rcode = nf90_inq_varid(ncidv, 'VWND', varidv) 2011 IF (rcode.NE.NF_NOERR) THEN 2012 abort_message='Nudging: error -> no VWND variable in file v.nc' 2013 CALL abort_gcm(modname,abort_message,1) 2014 ENDIF 2015 write(*,*)trim(modname)//' ncidv,varidv',ncidv,varidv 2016 if (ncidpl.eq.-99) ncidpl=ncidv 2017 endif 1923 2018 ! Temperature 1924 2019 if (guide_T) then 1925 1926 1927 print *,'Guide: probleme -> pas de fichierT.nc'1928 1929 1930 1931 1932 print *,'Guide: probleme -> pas de variable AIR, fichierT.nc'1933 1934 1935 print*,'ncidT,varidT',ncidt,varidt1936 2020 rcode = nf90_open('T.nc', nf90_nowrite, ncidt) 2021 IF (rcode.NE.NF_NOERR) THEN 2022 abort_message='Nudging: error -> no file T.nc' 2023 CALL abort_gcm(modname,abort_message,1) 2024 ENDIF 2025 rcode = nf90_inq_varid(ncidt, 'AIR', varidt) 2026 IF (rcode.NE.NF_NOERR) THEN 2027 abort_message='Nudging: error -> no AIR variable in file T.nc' 2028 CALL abort_gcm(modname,abort_message,1) 2029 ENDIF 2030 write(*,*)trim(modname)//' ncidT,varidT',ncidt,varidt 2031 if (ncidpl.eq.-99) ncidpl=ncidt 1937 2032 endif 1938 2033 ! Humidite 1939 2034 if (guide_Q) then 1940 1941 1942 print *,'Guide: probleme -> pas de fichierhur.nc'1943 1944 1945 1946 1947 print *,'Guide: probleme -> pas de variable RH, fichierhur.nc'1948 1949 1950 print*,'ncidQ,varidQ',ncidQ,varidQ1951 2035 rcode = nf90_open('hur.nc', nf90_nowrite, ncidQ) 2036 IF (rcode.NE.NF_NOERR) THEN 2037 abort_message='Nudging: error -> no file hur.nc' 2038 CALL abort_gcm(modname,abort_message,1) 2039 ENDIF 2040 rcode = nf90_inq_varid(ncidQ, 'RH', varidQ) 2041 IF (rcode.NE.NF_NOERR) THEN 2042 abort_message='Nudging: error -> no RH,variable in file hur.nc' 2043 CALL abort_gcm(modname,abort_message,1) 2044 ENDIF 2045 write(*,*)trim(modname)//' ncidQ,varidQ',ncidQ,varidQ 2046 if (ncidpl.eq.-99) ncidpl=ncidQ 1952 2047 endif 1953 2048 ! Pression de surface 1954 2049 if ((guide_P).OR.(guide_plevs.EQ.1)) then 1955 1956 1957 print *,'Guide: probleme -> pas de fichierps.nc'1958 1959 1960 1961 1962 print *,'Guide: probleme -> pas de variable SP, fichierps.nc'1963 1964 1965 print*,'ncidps,varidps',ncidps,varidps2050 rcode = nf90_open('ps.nc', nf90_nowrite, ncidps) 2051 IF (rcode.NE.NF_NOERR) THEN 2052 abort_message='Nudging: error -> no file ps.nc' 2053 CALL abort_gcm(modname,abort_message,1) 2054 ENDIF 2055 rcode = nf90_inq_varid(ncidps, 'SP', varidps) 2056 IF (rcode.NE.NF_NOERR) THEN 2057 abort_message='Nudging: error -> no SP variable in file ps.nc' 2058 CALL abort_gcm(modname,abort_message,1) 2059 ENDIF 2060 write(*,*)trim(modname)//' ncidps,varidps',ncidps,varidps 1966 2061 endif 1967 2062 ! Coordonnee verticale 1968 2063 if (guide_plevs.EQ.0) then 1969 1970 1971 print*,'ncidpl,varidpl',ncidpl,varidpl2064 rcode = nf90_inq_varid(ncidpl, 'LEVEL', varidpl) 2065 IF (rcode.NE.0) rcode = nf90_inq_varid(ncidpl, 'PRESSURE', varidpl) 2066 write(*,*)trim(modname)//' ncidpl,varidpl',ncidpl,varidpl 1972 2067 endif 1973 2068 ! Coefs ap, bp pour calcul de la pression aux differents niveaux … … 2163 2258 REAL zu(ip1jmp1),zv(ip1jm), zt(iip1, jjp1), zq(iip1, jjp1) 2164 2259 REAL, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: field_glo 2260 CHARACTER(LEN=20),PARAMETER :: modname="guide_out" 2165 2261 2166 2262 !$OMP MASTER … … 2169 2265 !$OMP BARRIER 2170 2266 2171 print*,'gvide_out apresallocation ',hsize,vsize2267 ! write(*,*)trim(modname)//' after allocation ',hsize,vsize 2172 2268 2173 2269 IF (hsize==jjp1) THEN … … 2177 2273 ENDIF 2178 2274 2179 print*,'guide_out apresgather '2275 ! write(*,*)trim(modname)//' after gather ' 2180 2276 CALL Gather_field_u(alpha_u,zu,1) 2181 2277 CALL Gather_field_u(alpha_t,zt,1) … … 2347 2443 !$OMP BARRIER 2348 2444 2349 RETURN2350 2351 2445 END SUBROUTINE guide_out 2352 2446 -
LMDZ6/branches/Ocean_skin/libf/dyn3dmem/iniacademic_loc.F90
r3605 r4013 73 73 LOGICAL ok_geost ! Initialisation vent geost. ou nul 74 74 LOGICAL ok_pv ! Polar Vortex 75 REAL phi_pv,dphi_pv,gam_pv ! Constantes pour polar vortex75 REAL phi_pv,dphi_pv,gam_pv,tetanoise ! Constantes pour polar vortex 76 76 77 77 real zz,ran1 … … 122 122 CALL inigeom 123 123 CALL inifilr 124 125 ! Initialize pressure and mass field if read_start=.false. 126 IF (.NOT. read_start) THEN 127 ! allocate global fields: 128 ! allocate(vcov_glo(ip1jm,llm)) 129 allocate(ucov_glo(ip1jmp1,llm)) 130 allocate(teta_glo(ip1jmp1,llm)) 131 allocate(ps_glo(ip1jmp1)) 132 allocate(masse_glo(ip1jmp1,llm)) 133 allocate(phis_glo(ip1jmp1)) 134 135 ! surface pressure 136 if (iflag_phys>2) then 137 ! specific value for CMIP5 aqua/terra planets 138 ! "Specify the initial dry mass to be equivalent to 139 ! a global mean surface pressure (101325 minus 245) Pa." 140 ps_glo(:)=101080. 141 else 142 ! use reference surface pressure 143 ps_glo(:)=preff 144 endif 145 146 ! ground geopotential 147 phis_glo(:)=0. 148 149 CALL pression ( ip1jmp1, ap, bp, ps_glo, p ) 150 if (pressure_exner) then 151 CALL exner_hyb( ip1jmp1, ps_glo, p, pks, pk ) 152 else 153 call exner_milieu(ip1jmp1,ps_glo,p,pks,pk) 154 endif 155 CALL massdair(p,masse_glo) 156 ENDIF 157 124 158 125 159 if (llm == 1) then … … 172 206 gam_pv=4. ! -dT/dz vortex (in K/km) 173 207 CALL getin('gam_pv',gam_pv) 208 tetanoise=0.005 209 CALL getin('tetanoise',tetanoise) 174 210 175 211 ! 2. Initialize fields towards which to relax … … 224 260 ! 3. Initialize fields (if necessary) 225 261 IF (.NOT. read_start) THEN 226 ! allocate global fields:227 ! allocate(vcov_glo(ip1jm,llm))228 allocate(ucov_glo(ip1jmp1,llm))229 allocate(teta_glo(ip1jmp1,llm))230 allocate(ps_glo(ip1jmp1))231 allocate(masse_glo(ip1jmp1,llm))232 allocate(phis_glo(ip1jmp1))233 234 ! surface pressure235 if (iflag_phys>2) then236 ! specific value for CMIP5 aqua/terra planets237 ! "Specify the initial dry mass to be equivalent to238 ! a global mean surface pressure (101325 minus 245) Pa."239 ps_glo(:)=101080.240 else241 ! use reference surface pressure242 ps_glo(:)=preff243 endif244 245 ! ground geopotential246 phis_glo(:)=0.247 248 CALL pression ( ip1jmp1, ap, bp, ps_glo, p )249 if (pressure_exner) then250 CALL exner_hyb( ip1jmp1, ps_glo, p, pks, pk )251 else252 call exner_milieu(ip1jmp1,ps_glo,p,pks,pk)253 endif254 CALL massdair(p,masse_glo)255 256 262 ! bulk initialization of temperature 257 teta_glo(:,:)=tetarappel(:,:) 258 263 IF (iflag_phys>10000) THEN 264 ! Particular case to impose a constant temperature T0=0.01*iflag_phys 265 teta_glo(:,:)= 0.01*iflag_phys/(pk(:,:)/cpp) 266 ELSE 267 teta_glo(:,:)=tetarappel(:,:) 268 ENDIF 259 269 ! geopotential 260 270 CALL geopot(ip1jmp1,teta_glo,pk,pks,phis_glo,phi) … … 306 316 do l=1,llm 307 317 do ij=iip2,ip1jm 308 teta_glo(ij,l)=teta_glo(ij,l)*(1.+ 0.005*ran1(idum))318 teta_glo(ij,l)=teta_glo(ij,l)*(1.+tetanoise*ran1(idum)) 309 319 enddo 310 320 enddo -
LMDZ6/branches/Ocean_skin/libf/dyn3dmem/leapfrog_loc.F
r3798 r4013 1538 1538 c$OMP END MASTER 1539 1539 1540 if (ok_guide) then 1541 ! set ok_guide to false to avoid extra output 1542 ! in following forward step 1543 ok_guide=.false. 1544 endif 1545 1540 1546 #ifdef INCA 1541 if (type_trac == 'inca' ) then1547 if (type_trac == 'inca' .OR. type_trac == 'inco') then 1542 1548 call finalize_inca 1543 1549 endif … … 1594 1600 1595 1601 #ifdef INCA 1596 if (type_trac == 'inca' ) then1602 if (type_trac == 'inca' .OR. type_trac == 'inco') then 1597 1603 call finalize_inca 1598 1604 endif … … 1681 1687 & vcov,ucov,teta,q,masse,ps) 1682 1688 ! endif ! of if (planet_type.eq."earth") 1689 if (ok_guide) then 1690 ! set ok_guide to false to avoid extra output 1691 ! in following forward step 1692 ok_guide=.false. 1693 endif 1683 1694 1684 1695 ! CLOSE(99) … … 1750 1761 1751 1762 #ifdef INCA 1752 if (type_trac == 'inca' ) then1763 if (type_trac == 'inca' .OR. type_trac == 'inco') then 1753 1764 call finalize_inca 1754 1765 endif … … 1827 1838 . vcov,ucov,teta,q,masse,ps) 1828 1839 ! endif ! of if (planet_type.eq."earth") 1840 if (ok_guide) then 1841 ! set ok_guide to false to avoid extra output 1842 ! in following forward step 1843 ok_guide=.false. 1844 endif 1845 1829 1846 ENDIF ! of IF(itau.EQ.itaufin) 1830 1847 … … 1845 1862 1846 1863 #ifdef INCA 1847 if (type_trac == 'inca' ) then1864 if (type_trac == 'inca' .OR. type_trac == 'inco') then 1848 1865 call finalize_inca 1849 1866 endif -
LMDZ6/branches/Ocean_skin/libf/dyn3dmem/parallel_lmdz.F90
r2771 r4013 12 12 INTEGER,PARAMETER :: halo_max=3 13 13 14 LOGICAL,SAVE :: using_mpi 15 LOGICAL,SAVE :: using_omp 14 LOGICAL,SAVE :: using_mpi ! .true. if using MPI 15 LOGICAL,SAVE :: using_omp ! .true. if using OpenMP 16 LOGICAL,SAVE :: is_master ! .true. if the core is both MPI & OpenMP master 17 !$OMP THREADPRIVATE(is_master) 16 18 17 19 integer, save :: mpi_size … … 248 250 !$OMP END PARALLEL 249 251 CALL create_distrib(jj_nb_para,current_dist) 252 253 IF ((mpi_rank==0).and.(omp_rank==0)) THEN 254 is_master=.true. 255 ELSE 256 is_master=.false. 257 ENDIF 250 258 251 259 end subroutine init_parallel
Note: See TracChangeset
for help on using the changeset viewer.