! $Id$ ! ! MODULE_DOC: no variable $\uv$: useful for kinematic dynamo runs. ! !** AUTOMATIC CPARAM.INC GENERATION **************************** ! Declare (for generation of cparam.inc) the number of f array ! variables and auxiliary variables added by this module ! ! CPARAM logical, parameter :: lhydro = .false. ! CPARAM logical, parameter :: lhydro_kinematic = .false. ! MVAR CONTRIBUTION 0 ! MAUX CONTRIBUTION 0 ! ! PENCILS PROVIDED uu(3); u2; oo(3); ou; oxu(3); uij(3,3); sij(3,3); sij2 ! PENCILS PROVIDED divu; uij5(3,3); graddivu(3); ugu(3); ogu(3) ! PENCILS PROVIDED del2u(3), curlo(3), uu_advec(3) ! PENCILS PROVIDED lorentz_gamma2; lorentz_gamma; ss_rel(3); divss_rel ! !*************************************************************** module Hydro ! use Cparam use Cdata use General, only: keep_compiler_quiet use Messages ! implicit none ! include 'record_types.h' include 'hydro.h' ! real, dimension (mx,3) :: uumx=0. real, dimension (mz,3) :: uumz=0. real, dimension (mz,3) :: uumzg=0. real, dimension (mx,my,3) :: uumxy=0. real, dimension (mx,mz,3) :: uumxz=0. ! real :: u_out_kep=0.0 logical, target :: lpressuregradient_gas=.false. logical :: lcalc_uumean=.false.,lupw_uu=.false. logical :: lcalc_uumeanx=.false.,lcalc_uumeanz=.false. logical :: lcalc_uumeanxy=.false.,lcalc_uumeanxz=.false. ! real, allocatable, dimension (:,:) :: KS_k,KS_A,KS_B !or through whole field for each wavenumber? real, allocatable, dimension (:) :: KS_omega !or through whole field for each wavenumber? integer :: KS_modes = 3 real, allocatable, dimension (:) :: Zl,dZldr,Pl,dPldtheta real :: ampl_fcont_uu=1., w_sld_cs=0.0 logical :: lforcing_cont_uu=.false. integer :: pushpars2c, pushdiags2c ! should be procedure pointer (F2003) ! integer :: idiag_u2m=0,idiag_um2=0,idiag_oum=0,idiag_o2m=0 integer :: idiag_uxpt=0,idiag_uypt=0,idiag_uzpt=0 integer :: idiag_dtu=0,idiag_urms=0,idiag_umax=0,idiag_uzrms=0 integer :: idiag_uzmax=0,idiag_orms=0,idiag_omax=0 integer :: idiag_ux2m=0,idiag_uy2m=0,idiag_uz2m=0 integer :: idiag_uxuym=0,idiag_uxuzm=0,idiag_uyuzm=0,idiag_oumphi=0 integer :: idiag_ruxm=0,idiag_ruym=0,idiag_ruzm=0,idiag_rumax=0 integer :: idiag_uxmz=0,idiag_uymz=0,idiag_uzmz=0,idiag_umx=0 integer :: idiag_umy=0,idiag_umz=0,idiag_uxmxy=0,idiag_uymxy=0,idiag_uzmxy=0 integer :: idiag_Marms=0,idiag_Mamax=0,idiag_divu2m=0,idiag_epsK=0 integer :: idiag_urmphi=0,idiag_upmphi=0,idiag_uzmphi=0,idiag_u2mphi=0 integer :: idiag_ekintot=0, idiag_ekin=0 ! contains !*********************************************************************** subroutine register_hydro ! ! Initialise variables which should know that we solve the hydro ! equations: iuu, etc; increase nvar accordingly. ! ! 6-nov-01/wolf: coded ! use Mpicomm, only: lroot use SharedVariables, only: put_shared_variable ! integer :: ierr ! ! Identify version number (generated automatically by SVN). ! if (lroot) call svn_id( & "$Id$") ! ! Share lpressuregradient_gas so Entropy module knows whether to apply ! pressure gradient or not. ! call put_shared_variable('lpressuregradient_gas',lpressuregradient_gas,caller='register_hydro') ! endsubroutine register_hydro !*********************************************************************** subroutine initialize_hydro(f) ! ! Perform any post-parameter-read initialization i.e. calculate derived ! parameters. ! ! 24-nov-02/tony: coded ! use FArrayManager ! real, dimension (mx,my,mz,mfarray) :: f ! if (kinflow=='KS') then ! call random_isotropic_KS_setup(-5./3.,1.,(nxgrid)/2.) ! ! Use constant values for testing KS model code with 3 ! specific modes. ! call random_isotropic_KS_setup_test endif ! ! Register an extra aux slot for uu if requested (so uu is written ! to snapshots and can be easily analyzed later). For this to work you ! must reserve enough auxiliary workspace by setting, for example, ! ! MAUX CONTRIBUTION 3 ! in the beginning of your src/cparam.local file, *before* setting ! ncpus, nprocy, etc. ! ! After a reload, we need to rewrite index.pro, but the auxiliary ! arrays are already allocated and must not be allocated again. ! if (lkinflow_as_aux) then if (iuu==0) then call farray_register_auxiliary('uu',iuu,vector=3) iux=iuu iuy=iuu+1 iuz=iuu+2 else if (lroot .and. (ip<14)) print*, 'initialize_hydro: iuu = ', iuu call farray_index_append('iuu',iuu,3) endif endif ! vel_spec=.false.; oo_spec=.false.; vel_phispec=.false. uxy_spec=.false.; ou_spec=.false.; uzs_spec=.false. ou_phispec=.false.; ou_kzspec=.false.; ouout_polar=.false. uut_spec=.false.; uut_polar=.false.; ouout_spec=.false. out_spec=.false.; uot_spec=.false. ub_spec=.false.; uxj_spec=.false.; EMF_spec=.false. call keep_compiler_quiet(f) ! endsubroutine initialize_hydro !*********************************************************************** subroutine calc_means_hydro(f) ! ! dummy routine ! ! 14-oct-13/MR: coded ! real, dimension (mx,my,mz,mfarray), intent(IN) :: f call keep_compiler_quiet(f) ! endsubroutine calc_means_hydro !*********************************************************************** subroutine init_uu(f) ! ! initialise uu and lnrho; called from start.f90 ! Should be located in the Hydro module, if there was one. ! ! 7-jun-02/axel: adapted from hydro ! real, dimension (mx,my,mz,mfarray) :: f ! call keep_compiler_quiet(f) ! endsubroutine init_uu !*********************************************************************** subroutine pencil_criteria_hydro ! ! All pencils that the Hydro module depends on are specified here. ! ! 20-nov-04/anders: coded ! 1-jul-09/axel: added more for kinflow ! ! pencils for kinflow ! if (kinflow/='') then lpenc_requested(i_uu)=.true. if (kinflow=='eddy') then lpenc_requested(i_rcyl_mn)=.true. lpenc_requested(i_rcyl_mn1)=.true. endif endif ! ! disgnostic pencils ! if (idiag_urms/=0 .or. idiag_umax/=0 .or. idiag_u2m/=0 .or. & idiag_um2/=0) lpenc_diagnos(i_u2)=.true. if (idiag_oum/=0) lpenc_diagnos(i_ou)=.true. ! endsubroutine pencil_criteria_hydro !*********************************************************************** subroutine pencil_interdep_hydro(lpencil_in) ! ! Interdependency among pencils from the Hydro module is specified here ! ! 20-nov-04/anders: coded ! logical, dimension (npencils) :: lpencil_in ! !ajwm May be overkill... Perhaps only needed for certain kinflow? if (lpencil_in(i_uglnrho)) then lpencil_in(i_uu)=.true. lpencil_in(i_glnrho)=.true. endif if (lpencil_in(i_ugrho)) then lpencil_in(i_uu)=.true. lpencil_in(i_grho)=.true. endif if (lpencil_in(i_uij5glnrho)) then lpencil_in(i_uij5)=.true. lpencil_in(i_glnrho)=.true. endif if (lpencil_in(i_u2)) lpencil_in(i_uu)=.true. ! oo if (lpencil_in(i_ou) .or. lpencil_in(i_oxu)) then lpencil_in(i_uu)=.true. lpencil_in(i_oo)=.true. endif ! endsubroutine pencil_interdep_hydro !*********************************************************************** subroutine calc_pencils_hydro_std(f,p) ! ! Envelope adjusting calc_pencils_hydro_pencpar to the standard use with ! lpenc_loc=lpencil ! ! 21-sep-13/MR : coded ! real, dimension (mx,my,mz,mfarray),intent(IN) :: f type (pencil_case), intent(OUT):: p ! call calc_pencils_hydro_pencpar(f,p,lpencil) ! endsubroutine calc_pencils_hydro_std !*********************************************************************** subroutine calc_pencils_hydro_pencpar(f,p,lpenc_loc) ! ! Calculate Hydro pencils. ! Most basic pencils should come first, as others may depend on them. ! ! 08-nov-04/tony: coded ! use Diagnostics, only: sum_mn_name, max_mn_name, integrate_mn_name use General, only: random_number_wrapper use Sub, only: quintic_step, quintic_der_step, dot_mn, dot2_mn ! real, dimension (mx,my,mz,mfarray) :: f type (pencil_case) :: p logical, dimension(:) :: lpenc_loc integer :: kk ! intent(in) :: f, lpenc_loc intent(inout) :: p ! uu if (lpenc_loc(i_uu)) p%uu=0.0 ! u2 if (lpenc_loc(i_u2)) p%u2=0.0 ! oo if (lpenc_loc(i_oo)) p%oo=0.0 ! ou if (lpenc_loc(i_ou)) p%ou=0.0 ! oxu if (lpenc_loc(i_oxu)) p%oxu=0.0 ! uij if (lpenc_loc(i_uij)) p%uij=0.0 ! sij if (lpenc_loc(i_sij)) p%sij=0.0 ! sij2 if (lpenc_loc(i_sij2)) p%sij2=0.0 ! divu if (lpenc_loc(i_divu)) p%divu=0.0 ! uij5 if (lpenc_loc(i_uij5)) p%uij5=0.0 ! graddivu if (lpenc_loc(i_graddivu)) p%graddivu=0.0 ! ugu if (lpenc_loc(i_ugu)) p%ugu=0.0 ! ogu if (lpenc_loc(i_ogu)) p%ogu=0.0 ! del2u if (lpenc_loc(i_del2u)) p%del2u=0.0 ! curlo if (lpenc_loc(i_curlo)) p%curlo=0.0 ! relativistic stuff if (lpenc_loc(i_lorentz_gamma2)) p%lorentz_gamma2=0. if (lpenc_loc(i_lorentz_gamma)) p%lorentz_gamma=0. if (lpenc_loc(i_ss_rel)) p%ss_rel=0. if (lpenc_loc(i_divss_rel)) p%divss_rel=0. ! ! Calculate maxima and rms values for diagnostic purposes ! if (ldiagnos) then if (idiag_urms/=0) call sum_mn_name(p%u2,idiag_urms,lsqrt=.true.) if (idiag_umax/=0) call max_mn_name(p%u2,idiag_umax,lsqrt=.true.) if (idiag_uzrms/=0) & call sum_mn_name(p%uu(:,3)**2,idiag_uzrms,lsqrt=.true.) if (idiag_uzmax/=0) & call max_mn_name(p%uu(:,3)**2,idiag_uzmax,lsqrt=.true.) if (idiag_u2m/=0) call sum_mn_name(p%u2,idiag_u2m) if (idiag_um2/=0) call max_mn_name(p%u2,idiag_um2) ! if (idiag_ekin/=0) call sum_mn_name(.5*p%rho*p%u2,idiag_ekin) if (idiag_ekintot/=0) & call integrate_mn_name(.5*p%rho*p%u2,idiag_ekintot) endif ! call keep_compiler_quiet(f) ! endsubroutine calc_pencils_hydro_pencpar !*********************************************************************** subroutine hydro_before_boundary(f) ! ! Actions to take before boundary conditions are set, dummy routine. ! ! 17-dec-2010/Bourdin.KIS: coded ! real, dimension (mx,my,mz,mfarray), intent(inout) :: f ! call keep_compiler_quiet(f) ! endsubroutine hydro_before_boundary !*********************************************************************** subroutine duu_dt(f,df,p) ! ! velocity evolution, dummy routine ! ! 7-jun-02/axel: adapted from hydro ! use Diagnostics, only: sum_mn_name, save_name ! real, dimension (mx,my,mz,mfarray) :: f real, dimension (mx,my,mz,mvar) :: df type (pencil_case) :: p ! intent(in) :: df,p intent(out) :: f ! ! Calculate maxima and rms values for diagnostic purposes ! if (ldiagnos) then if (headtt.or.ldebug) print*,'duu_dt: diagnostics ...' if (idiag_oum/=0) call sum_mn_name(p%ou,idiag_oum) !if (idiag_orms/=0) call sum_mn_name(p%o2,idiag_orms,lsqrt=.true.) !if (idiag_omax/=0) call max_mn_name(p%o2,idiag_omax,lsqrt=.true.) ! ! kinetic field components at one point (=pt) ! if (lroot.and.m==mpoint.and.n==npoint) then if (idiag_uxpt/=0) call save_name(p%uu(lpoint-nghost,1),idiag_uxpt) if (idiag_uypt/=0) call save_name(p%uu(lpoint-nghost,2),idiag_uypt) if (idiag_uzpt/=0) call save_name(p%uu(lpoint-nghost,3),idiag_uzpt) endif endif ! call keep_compiler_quiet(f,df) ! endsubroutine duu_dt !*********************************************************************** subroutine calc_diagnostics_hydro(f,p) real, dimension(:,:,:,:) :: f type(pencil_case), intent(in) :: p call keep_compiler_quiet(f) call keep_compiler_quiet(p) endsubroutine calc_diagnostics_hydro !****************************************************************************** subroutine df_diagnos_hydro(df,p) use Diagnostics, only: sum_mn_name type(pencil_case), intent(in) :: p real, dimension(:,:,:,:) :: df call keep_compiler_quiet(df) call keep_compiler_quiet(p) endsubroutine df_diagnos_hydro !*********************************************************************** subroutine time_integrals_hydro(f,p) ! ! 1-jul-08/axel: dummy ! real, dimension (mx,my,mz,mfarray) :: f type (pencil_case) :: p ! intent(in) :: f,p ! call keep_compiler_quiet(f) call keep_compiler_quiet(p) ! endsubroutine time_integrals_hydro !*********************************************************************** subroutine coriolis_cartesian(df,uu,velind) ! ! coriolis terms for cartesian geometry ! ! 30-oct-09/MR: outsourced, parameter velind added ! checked to be an equivalent change by auto-test conv-slab-noequi, mdwarf ! real, dimension (mx,my,mz,mvar), intent(out) :: df real, dimension (nx,3), intent(in) :: uu integer, intent(in) :: velind ! call keep_compiler_quiet(df) call keep_compiler_quiet(uu) call keep_compiler_quiet(velind) ! endsubroutine coriolis_cartesian !*********************************************************************** subroutine hydro_after_boundary(f) ! ! dummy routine ! real, dimension (mx,my,mz,mfarray) :: f ! call keep_compiler_quiet(f) ! ! Slope limited diffusion: update characteristic speed ! Not staggered yet ! if (lslope_limit_diff .and. llast) then f(:,:,:,isld_char)=0. endif ! endsubroutine hydro_after_boundary !*********************************************************************** subroutine random_isotropic_KS_setup_tony(initpower,kmin,kmax) ! ! produces random, isotropic field from energy spectrum following the ! KS method (Malik and Vassilicos, 1999.) ! ! more to do; unsatisfactory so far - at least for a steep power-law ! energy spectrum ! ! 27-may-05/tony: modified from snod's KS hydro initial ! 03-feb-06/weezy: Tony's code doesn't appear to have the ! correct periodicity. ! renamed from random_isotropic_KS_setup ! use Sub, only: cross use General, only: random_number_wrapper ! integer :: modeN ! real, dimension (3) :: k_unit real, dimension (3) :: e1,e2 real, dimension (6) :: r real, dimension (3) ::j,l !get rid of this - these replace ee,ee1 real :: initpower,kmin,kmax real, dimension (KS_modes) :: k,dk,energy,ps real :: theta,phi,alpha,beta real :: a,mkunit real :: newthet,newphi !get rid of this line if there's no change ! allocate(KS_k(3,KS_modes)) allocate(KS_A(3,KS_modes)) allocate(KS_B(3,KS_modes)) allocate(KS_omega(KS_modes)) ! ! minlen=Lxyz(1)/(nx-1) ! kmax=2.*pi/minlen ! KS_modes=int(0.5*(nx-1)) ! hh=Lxyz(1)/(nx-1) ! pta=(nx)**(1.0/(nx-1)) ! do modeN=1,KS_modes ! ggt=(kkmax-kkmin)/(KS_modes-1) ! ggt=(kkmax/kkmin)**(1./(KS_modes-1)) ! k(modeN)=kmin+(ggt*(modeN-1)) ! k(modeN)=(modeN+3)*2*pi/Lxyz(1) ! k(modeN)=kkmin*(ggt**(modeN-1) ! enddo ! ! do modeN=1,KS_modes ! if (modeN==1)delk(modeN)=(k(modeN+1)-K(modeN)) ! if (modeN==KS_modes)delk(modeN)=(k(modeN)-k(modeN-1)) ! if (modeN>1.and.modeN1.and.modeN1.and.modeN1.and.modeN