Skip to content
Snippets Groups Projects
Commit bce3118a authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann :seedling:
Browse files

small changes

parent 1a0c3bee
No related branches found
No related tags found
No related merge requests found
...@@ -10,11 +10,11 @@ IMPLICIT NONE ...@@ -10,11 +10,11 @@ IMPLICIT NONE
INTEGER :: status(MPI_STATUS_SIZE), source, dest, count, ipg INTEGER :: status(MPI_STATUS_SIZE), source, dest, count, ipg
PUBLIC :: update_ghosts PUBLIC :: update_ghosts_moments, update_ghosts_phi
CONTAINS CONTAINS
SUBROUTINE update_ghosts SUBROUTINE update_ghosts_moments
CALL cpu_time(t0_ghost) CALL cpu_time(t0_ghost)
IF (num_procs_p .GT. 1) THEN ! Do it only if we share the p IF (num_procs_p .GT. 1) THEN ! Do it only if we share the p
...@@ -27,12 +27,20 @@ SUBROUTINE update_ghosts ...@@ -27,12 +27,20 @@ SUBROUTINE update_ghosts
IF(KIN_E) & IF(KIN_E) &
CALL update_ghosts_z_e CALL update_ghosts_z_e
CALL update_ghosts_z_i CALL update_ghosts_z_i
CALL update_ghosts_z_phi
ENDIF ENDIF
tc_ghost = tc_ghost + (t1_ghost - t0_ghost) tc_ghost = tc_ghost + (t1_ghost - t0_ghost)
END SUBROUTINE update_ghosts END SUBROUTINE update_ghosts_moments
SUBROUTINE update_ghosts_phi
CALL cpu_time(t0_ghost)
IF(Nz .GT. 1) THEN
CALL update_ghosts_z_phi
ENDIF
tc_ghost = tc_ghost + (t1_ghost - t0_ghost)
END SUBROUTINE update_ghosts_phi
!Communicate p+1, p+2 moments to left neighboor and p-1, p-2 moments to right one !Communicate p+1, p+2 moments to left neighboor and p-1, p-2 moments to right one
! [a b|C D|e f] : proc n has moments a to f where a,b,e,f are ghosts ! [a b|C D|e f] : proc n has moments a to f where a,b,e,f are ghosts
......
...@@ -8,7 +8,7 @@ SUBROUTINE inital ...@@ -8,7 +8,7 @@ SUBROUTINE inital
USE time_integration, ONLY: set_updatetlevel USE time_integration, ONLY: set_updatetlevel
USE collision, ONLY: load_COSOlver_mat, cosolver_coll USE collision, ONLY: load_COSOlver_mat, cosolver_coll
USE closure, ONLY: apply_closure_model USE closure, ONLY: apply_closure_model
USE ghosts, ONLY: update_ghosts USE ghosts, ONLY: update_ghosts_moments, update_ghosts_phi
USE restarts, ONLY: load_moments, job2load USE restarts, ONLY: load_moments, job2load
USE numerics, ONLY: play_with_modes, save_EM_ZF_modes USE numerics, ONLY: play_with_modes, save_EM_ZF_modes
USE processing, ONLY: compute_fluid_moments USE processing, ONLY: compute_fluid_moments
...@@ -23,8 +23,9 @@ SUBROUTINE inital ...@@ -23,8 +23,9 @@ SUBROUTINE inital
IF ( job2load .GE. 0 ) THEN IF ( job2load .GE. 0 ) THEN
IF (my_id .EQ. 0) WRITE(*,*) 'Load moments' IF (my_id .EQ. 0) WRITE(*,*) 'Load moments'
CALL load_moments ! get N_0 CALL load_moments ! get N_0
CALL update_ghosts_moments
CALL poisson ! compute phi_0=phi(N_0) CALL poisson ! compute phi_0=phi(N_0)
CALL update_ghosts CALL update_ghosts_phi
! through initialization ! through initialization
ELSE ELSE
SELECT CASE (INIT_OPT) SELECT CASE (INIT_OPT)
...@@ -32,31 +33,35 @@ SUBROUTINE inital ...@@ -32,31 +33,35 @@ SUBROUTINE inital
CASE ('phi') CASE ('phi')
IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy phi' IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy phi'
CALL init_phi CALL init_phi
CALL update_ghosts CALL update_ghosts_phi
! set moments_00 (GC density) with noise and compute phi afterwards ! set moments_00 (GC density) with noise and compute phi afterwards
CASE('mom00') CASE('mom00')
IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy gyrocenter density' IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy gyrocenter density'
CALL init_gyrodens ! init only gyrocenter density CALL init_gyrodens ! init only gyrocenter density
CALL update_ghosts CALL update_ghosts_moments
CALL poisson CALL poisson
CALL update_ghosts_phi
! init all moments randomly (unadvised) ! init all moments randomly (unadvised)
CASE('allmom') CASE('allmom')
IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy moments' IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy moments'
CALL init_moments ! init all moments CALL init_moments ! init all moments
CALL update_ghosts CALL update_ghosts_moments
CALL poisson CALL poisson
CALL update_ghosts_phi
! init a gaussian blob in gyrodens ! init a gaussian blob in gyrodens
CASE('blob') CASE('blob')
IF (my_id .EQ. 0) WRITE(*,*) '--init a blob' IF (my_id .EQ. 0) WRITE(*,*) '--init a blob'
CALL initialize_blob CALL initialize_blob
CALL update_ghosts CALL update_ghosts_moments
CALL poisson CALL poisson
CALL update_ghosts_phi
! init moments 00 with a power law similarly to GENE ! init moments 00 with a power law similarly to GENE
CASE('ppj') CASE('ppj')
IF (my_id .EQ. 0) WRITE(*,*) 'ppj init ~ GENE' IF (my_id .EQ. 0) WRITE(*,*) 'ppj init ~ GENE'
call init_ppj call init_ppj
CALL update_ghosts CALL update_ghosts_moments
CALL poisson CALL poisson
CALL update_ghosts_phi
END SELECT END SELECT
ENDIF ENDIF
! closure of j>J, p>P and j<0, p<0 moments ! closure of j>J, p>P and j<0, p<0 moments
...@@ -64,7 +69,8 @@ SUBROUTINE inital ...@@ -64,7 +69,8 @@ SUBROUTINE inital
CALL apply_closure_model CALL apply_closure_model
! ghosts for p parallelization ! ghosts for p parallelization
IF (my_id .EQ. 0) WRITE(*,*) 'Ghosts communication' IF (my_id .EQ. 0) WRITE(*,*) 'Ghosts communication'
CALL update_ghosts CALL update_ghosts_moments
CALL update_ghosts_phi
!! End of phi and moments initialization !! End of phi and moments initialization
! Save (kx,0) and (0,ky) modes for num exp ! Save (kx,0) and (0,ky) modes for num exp
......
...@@ -3,7 +3,7 @@ SUBROUTINE stepon ...@@ -3,7 +3,7 @@ SUBROUTINE stepon
USE advance_field_routine, ONLY: advance_time_level, advance_field, advance_moments USE advance_field_routine, ONLY: advance_time_level, advance_field, advance_moments
USE basic USE basic
USE closure USE closure
USE ghosts, ONLY: update_ghosts USE ghosts, ONLY: update_ghosts_moments, update_ghosts_phi
USE grid USE grid
USE model, ONLY : LINEARITY, KIN_E USE model, ONLY : LINEARITY, KIN_E
use prec_const use prec_const
...@@ -32,11 +32,11 @@ SUBROUTINE stepon ...@@ -32,11 +32,11 @@ SUBROUTINE stepon
! Closure enforcement of moments ! Closure enforcement of moments
CALL apply_closure_model CALL apply_closure_model
! Exchanges the ghosts values of N_n+1 ! Exchanges the ghosts values of N_n+1
CALL update_ghosts CALL update_ghosts_moments
! Update electrostatic potential phi_n = phi(N_n+1) ! Update electrostatic potential phi_n = phi(N_n+1)
CALL poisson CALL poisson
CALL update_ghosts_z_phi CALL update_ghosts_phi
! Numerical experiments ! Numerical experiments
! Store or cancel/maintain zonal modes artificially ! Store or cancel/maintain zonal modes artificially
...@@ -69,6 +69,8 @@ SUBROUTINE stepon ...@@ -69,6 +69,8 @@ SUBROUTINE stepon
END SUBROUTINE assemble_RHS END SUBROUTINE assemble_RHS
SUBROUTINE checkfield_all ! Check all the fields for inf or nan SUBROUTINE checkfield_all ! Check all the fields for inf or nan
USE fields, ONLY: phi, moments_e, moments_i
IMPLICIT NONE
! Execution time start ! Execution time start
CALL cpu_time(t0_checkfield) CALL cpu_time(t0_checkfield)
...@@ -99,6 +101,8 @@ SUBROUTINE stepon ...@@ -99,6 +101,8 @@ SUBROUTINE stepon
END SUBROUTINE checkfield_all END SUBROUTINE checkfield_all
SUBROUTINE anti_aliasing SUBROUTINE anti_aliasing
USE fields, ONLY: moments_e, moments_i
IMPLICIT NONE
IF(KIN_E)THEN IF(KIN_E)THEN
DO iz=izgs,izge DO iz=izgs,izge
DO ikx=ikxs,ikxe DO ikx=ikxs,ikxe
...@@ -126,6 +130,8 @@ SUBROUTINE stepon ...@@ -126,6 +130,8 @@ SUBROUTINE stepon
END SUBROUTINE anti_aliasing END SUBROUTINE anti_aliasing
SUBROUTINE enforce_symmetry ! Force X(k) = X(N-k)* complex conjugate symmetry SUBROUTINE enforce_symmetry ! Force X(k) = X(N-k)* complex conjugate symmetry
USE fields, ONLY: phi, moments_e, moments_i
IMPLICIT NONE
IF ( contains_ky0 ) THEN IF ( contains_ky0 ) THEN
! Electron moments ! Electron moments
IF(KIN_E) THEN IF(KIN_E) THEN
......
...@@ -11,7 +11,7 @@ system(['mkdir -p ',LOCALDIR]); ...@@ -11,7 +11,7 @@ system(['mkdir -p ',LOCALDIR]);
CMD = ['rsync ', LOCALDIR,'outputs* ',MISCDIR]; disp(CMD); CMD = ['rsync ', LOCALDIR,'outputs* ',MISCDIR]; disp(CMD);
system(CMD); system(CMD);
% Load outputs from jobnummin up to jobnummax % Load outputs from jobnummin up to jobnummax
JOBNUMMIN = 03; JOBNUMMAX = 20; JOBNUMMIN = 00; JOBNUMMAX = 20;
data = compile_results(MISCDIR,JOBNUMMIN,JOBNUMMAX); %Compile the results from first output found to JOBNUMMAX if existing data = compile_results(MISCDIR,JOBNUMMIN,JOBNUMMAX); %Compile the results from first output found to JOBNUMMAX if existing
data.localdir = LOCALDIR; data.localdir = LOCALDIR;
data.FIGDIR = LOCALDIR; data.FIGDIR = LOCALDIR;
...@@ -55,7 +55,7 @@ options.PLAN = 'xy'; ...@@ -55,7 +55,7 @@ options.PLAN = 'xy';
% options.PLAN = 'sx'; % options.PLAN = 'sx';
options.COMP = 1; options.COMP = 1;
% options.TIME = data.Ts5D(end-30:end); % options.TIME = data.Ts5D(end-30:end);
options.TIME = data.Ts3D(1:end); options.TIME = data.Ts3D(1:2:end);
% options.TIME = [350:600]; % options.TIME = [350:600];
data.EPS = 0.1; data.EPS = 0.1;
data.a = data.EPS * 2000; data.a = data.EPS * 2000;
...@@ -78,7 +78,7 @@ options.PLAN = 'kxky'; ...@@ -78,7 +78,7 @@ options.PLAN = 'kxky';
% options.NAME 'f_i'; % options.NAME 'f_i';
% options.PLAN = 'sx'; % options.PLAN = 'sx';
options.COMP = 1; options.COMP = 1;
options.TIME = [20 100 200 600 1900]; options.TIME = [20 30 40 60 70];
data.a = data.EPS * 2e3; data.a = data.EPS * 2e3;
fig = photomaton(data,options); fig = photomaton(data,options);
% save_figure(data,fig) % save_figure(data,fig)
......
...@@ -27,5 +27,4 @@ helazdir = '/home/ahoffman/HeLaZ/'; ...@@ -27,5 +27,4 @@ helazdir = '/home/ahoffman/HeLaZ/';
% outfile = 'shearless_cyclone/64x32x16x5x3_CBC_CO/64x32x16x5x3_CBC_LRGK'; % outfile = 'shearless_cyclone/64x32x16x5x3_CBC_CO/64x32x16x5x3_CBC_LRGK';
%% ZPINCH %% ZPINCH
outfile ='Zpinch_rerun/Kn_2.5_200x48x5x3'; outfile ='Zpinch_rerun/Kn_2.5_200x48x5x3';
run analysis_HeLaZ run analysis_HeLaZ
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment