Ignore:
Timestamp:
02/28/20 10:25:21 (4 years ago)
Author:
ymipsl
Message:

Add possibilty to set a white noise at restart. The amplitude of white noise is fixed by the folowing parameter that can be used in run.def :

  • etat0_ps_white_noise
  • etat0_theta_rhodz_white_noise
  • etat0_u_white_noise
  • etat0_q_white_noise

The value set the relative amplitude of the random perturbation.
ex :

etat0_ps_white_noise=1e-15 -> ps(ij)=ps(ij)*(1+1e-15*ran) where ran inside [0,1[

default perturbation is 0

YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/initial/etat0.f90

    r899 r1017  
    9595     
    9696    REAL(rstd),POINTER :: ps(:), mass(:,:) 
     97    REAL    :: etat0_ps_white_noise 
     98    REAL    :: etat0_theta_rhodz_white_noise 
     99    REAL    :: etat0_u_white_noise 
     100    REAL    :: etat0_q_white_noise 
    97101    LOGICAL :: autoinit_mass, collocated 
    98102    INTEGER :: ind 
     
    178182       END DO 
    179183    END IF 
     184     
     185    etat0_ps_white_noise=0. 
     186    CALL getin("etat0_ps_white_noise",etat0_ps_white_noise) 
     187    CALL add_white_noise(f_ps, etat0_ps_white_noise) 
     188 
     189    etat0_theta_rhodz_white_noise=0. 
     190    CALL getin("etat0_theta_rhodz_white_noise",etat0_theta_rhodz_white_noise) 
     191    CALL add_white_noise(f_theta_rhodz, etat0_theta_rhodz_white_noise) 
    180192  
     193    etat0_u_white_noise=0. 
     194    CALL getin("etat0_u_white_noise",etat0_u_white_noise) 
     195    CALL add_white_noise(f_u, etat0_u_white_noise) 
     196 
     197    etat0_q_white_noise=0. 
     198    CALL getin("etat0_q_white_noise",etat0_q_white_noise) 
     199    CALL add_white_noise(f_q, etat0_q_white_noise) 
     200     
    181201  END SUBROUTINE etat0 
    182202 
     203 
     204  SUBROUTINE add_white_noise(field, factor) 
     205  USE icosa 
     206  IMPLICIT NONE 
     207    TYPE(t_field),POINTER :: field(:)   ! INOUT 
     208    REAL,INTENT(IN) :: factor     
     209     
     210    INTEGER,ALLOCATABLE :: seed(:) 
     211    REAL,ALLOCATABLE :: random2d(:) 
     212    REAL,ALLOCATABLE :: random3d(:,:) 
     213    REAL,ALLOCATABLE :: random4d(:,:,:) 
     214    REAL,POINTER :: field2d(:) 
     215    REAL,POINTER :: field3d(:,:) 
     216    REAL,POINTER :: field4d(:,:,:) 
     217    INTEGER :: ind 
     218    INTEGER :: m 
     219     
     220    CALL RANDOM_SEED(SIZE=m) 
     221    ALLOCATE(seed(m)) 
     222     
     223    DO ind=1,ndomain 
     224      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
     225      seed=domloc_glo_ind(ind) ! to be reproducible 
     226      CALL RANDOM_SEED(PUT=seed) 
     227      IF (field(ind)%ndim==2) THEN 
     228        field2d=field(ind) 
     229        ALLOCATE(random2d(size(field2d,1))) 
     230        CALL RANDOM_NUMBER(random2d) 
     231        field2d=field2d*(1.+random2d*factor) 
     232        DEALLOCATE(random2d) 
     233      ELSE IF (field(ind)%ndim==3) THEN 
     234        field3d=field(ind) 
     235        ALLOCATE(random3d(size(field3d,1),size(field3d,2))) 
     236        CALL RANDOM_NUMBER(random3d) 
     237        field3d=field3d*(1.+random3d*factor) 
     238        DEALLOCATE(random3d) 
     239      ELSE IF (field(ind)%ndim==4) THEN 
     240        field4d=field(ind) 
     241        ALLOCATE(random4d(size(field4d,1),size(field4d,2),size(field4d,3))) 
     242        CALL RANDOM_NUMBER(random4d) 
     243        field4d=field4d*(1.+random4d*factor) 
     244        DEALLOCATE(random4d) 
     245      ENDIF 
     246    ENDDO 
     247     
     248  END SUBROUTINE 
     249     
     250     
    183251  SUBROUTINE etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q) 
    184252    USE theta2theta_rhodz_mod 
Note: See TracChangeset for help on using the changeset viewer.