!> \file initial2-0.4.f90 !!Initialisation du modele !< !> SUBROUTINE INITIAL2 !! Cette routine permet d'initialiser le modele. !! \author ... !! \date 19 Novembre 1999 !! @note Elle appelle toutes les routines d'initialisation des differents packages. !! @note C'est cette routine qui est appellee dans le main !! @note Used modules: !! @note - use module3D_phy !! @note - use param_phy_mod !< subroutine INITIAL2() USE module3D_phy USE param_phy_mod implicit none real,dimension(NZ) ::cord_vert ! INITIALISATION DES TABLEAUX cord_vert(1)=0. cord_vert(NZ)=1. do K=1,NZ if ((K.ne.1).and.(K.ne.NZ)) cord_vert(K)=(K-1.)/(NZ-1.) CDE(K)=1.-cord_vert(K) end do ABL(:,:)=0. BDOT(:,:)=0. BMELT(:,:)=0. EPSXX(:,:)=0. EPSYY(:,:)=0. EPSXY(:,:)=0. HWATER(:,:)=0. CALV(:,:)=0. HDOT(:,:)=0. HDOTWATER(:,:)=0. PDD(:,:)=0. SLOPE(:,:)=0. TBDOT(:,:)=0. TAUB(:,:)=0. TG(:,:)=0. UBX(:,:)=0. UBY(:,:)=0. UZK(:,:)=0. UXBAR(:,:)=0. UYBAR(:,:)=0. VBAR(:,:)=0. XX(:,:)=0. IBASE(:,:)=1 TPMP(:,:,1)=0 TPMP(:,:,NZ)=-0.00087*H(:,:) MK(:,:)=MK0(:,:) grzone(:,:)=.false. !-------Initialisation des fronts. FRONT(:,:) =0 FRONTFACEX(:,:)=0 FRONTFACEY(:,:)=0 !-------Initialisation des flot... devrait etre mise dans input_topo. ! en tout cas on le fait pour mismip do J=1,NY do I=1,NX if ((BSOC(I,J)+H(I,J)*RO/ROW -SEALEVEL).LT.0.) then FLOT(I,J)=.TRUE. else FLOT(I,J)=.FALSE. endif enddo enddo FLOTMX(:,:)=FLOT(:,:) FLOTMY(:,:)=FLOT(:,:) OKUMAT(:,:)=.FALSE. OKVMAT(:,:)=.FALSE. GZMX(:,:)=.FALSE. GZMY(:,:)=.FALSE. FLGZMX(:,:)=.FALSE. FLGZMY(:,:)=.FALSE. ILEMX(:,:)=.FALSE. ILEMY(:,:)=.FALSE. do J=2,NY do I=2,NX SDX(I,J)=(S(I,J)-S(I-1,J))/DX SDY(I,J)=(S(I,J)-S(I,J-1))/DX end do end do do K=1,NZ do I=1,NX do J=1,NY UX(I,J,K)=0. UY(I,J,K)=0. UZR(I,J,K)=0. T(I,J,K)=0. !CT(I,J,K)=6.62E7 !CP(I,J,K)=2009. end do end do end do do K=2,NZ-1 do I=1,NX do J=1,NY TPMP(I,J,K)=-0.00087*(K-1)/(NZ-1)*H(I,J) end do end do end do do K=NZ+1,NZ+NZM do I=1,NX do J=1,NY T(I,J,K)=0. end do end do end do end subroutine INITIAL2