Ignore:
Timestamp:
08/02/15 00:53:35 (9 years ago)
Author:
dubos
Message:

Move geopotential to timeloop, prepare for prognostic geopotential (NH)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/field.f90

    r295 r350  
    11MODULE field_mod 
    22  USE genmod 
     3  IMPLICIT NONE 
    34   
    45  INTEGER,PARAMETER :: field_T=1 
     
    4344  END INTERFACE 
    4445 
     46  PRIVATE :: allocate_field_ 
    4547 
    4648CONTAINS 
     
    4951  USE domain_mod 
    5052  USE omp_para 
    51   IMPLICIT NONE 
    5253    TYPE(t_field),POINTER :: field(:) 
     54    INTEGER,INTENT(IN) :: field_type 
     55    INTEGER,INTENT(IN) :: data_type 
     56    INTEGER,OPTIONAL :: dim1,dim2 
     57    CHARACTER(*), OPTIONAL :: name 
     58!$OMP BARRIER 
     59!$OMP MASTER 
     60    ALLOCATE(field(ndomain)) 
     61!$OMP END MASTER 
     62!$OMP BARRIER 
     63    CALL allocate_field_(field,field_type,data_type,dim1,dim2,name) 
     64  END SUBROUTINE allocate_field 
     65 
     66  SUBROUTINE allocate_fields(nfield,field,field_type,data_type,dim1,dim2,name) 
     67  USE domain_mod 
     68  USE omp_para 
     69    INTEGER,INTENT(IN) :: nfield 
     70    TYPE(t_field),POINTER :: field(:,:) 
     71    INTEGER,INTENT(IN) :: field_type 
     72    INTEGER,INTENT(IN) :: data_type 
     73    INTEGER,OPTIONAL :: dim1,dim2 
     74    CHARACTER(*), OPTIONAL :: name 
     75    INTEGER :: i 
     76!$OMP BARRIER 
     77!$OMP MASTER 
     78    ALLOCATE(field(ndomain,nfield)) 
     79!$OMP END MASTER 
     80!$OMP BARRIER 
     81    DO i=1,nfield 
     82       CALL allocate_field_(field(:,i),field_type,data_type,dim1,dim2,name) 
     83    END DO 
     84  END SUBROUTINE allocate_fields 
     85 
     86  SUBROUTINE allocate_field_(field,field_type,data_type,dim1,dim2,name) 
     87  USE domain_mod 
     88  USE omp_para 
     89  IMPLICIT NONE 
     90    TYPE(t_field) :: field(:) 
    5391    INTEGER,INTENT(IN) :: field_type 
    5492    INTEGER,INTENT(IN) :: data_type 
     
    5795    INTEGER :: ind 
    5896    INTEGER :: ii_size,jj_size 
    59  
    60 !$OMP BARRIER 
    61 !$OMP MASTER 
    62     ALLOCATE(field(ndomain)) 
    63 !$OMP END MASTER 
    64 !$OMP BARRIER 
    6597 
    6698    DO ind=1,ndomain 
     
    115147!$OMP BARRIER 
    116148    
    117   END SUBROUTINE allocate_field 
     149 END SUBROUTINE allocate_field_ 
    118150 
    119151  SUBROUTINE allocate_field_glo(field,field_type,data_type,dim1,dim2,name) 
     
    181213 
    182214  SUBROUTINE deallocate_field(field) 
     215    USE domain_mod 
     216    USE omp_para 
     217    IMPLICIT NONE 
     218    TYPE(t_field),POINTER :: field(:) 
     219    !$OMP BARRIER 
     220    CALL deallocate_field_(field) 
     221    !$OMP BARRIER 
     222    !$OMP MASTER 
     223    DEALLOCATE(field) 
     224    !$OMP END MASTER 
     225    !$OMP BARRIER 
     226  END SUBROUTINE deallocate_field 
     227   
     228  SUBROUTINE deallocate_fields(field) 
     229    USE domain_mod 
     230    USE omp_para 
     231    IMPLICIT NONE 
     232    TYPE(t_field),POINTER :: field(:,:) 
     233    INTEGER :: i 
     234    !$OMP BARRIER 
     235    DO i=1,SIZE(field,2) 
     236       CALL deallocate_field_(field(:,i)) 
     237    END DO 
     238    !$OMP BARRIER 
     239    !$OMP MASTER 
     240    DEALLOCATE(field) 
     241    !$OMP END MASTER 
     242    !$OMP BARRIER 
     243  END SUBROUTINE deallocate_fields 
     244 
     245  SUBROUTINE deallocate_field_(field) 
    183246  USE domain_mod 
    184247  USE omp_para 
    185248  IMPLICIT NONE 
    186     TYPE(t_field),POINTER :: field(:) 
     249    TYPE(t_field) :: field(:) 
    187250    INTEGER :: data_type 
    188251    INTEGER :: ind 
    189  
    190 !$OMP BARRIER 
    191252    DO ind=1,ndomain 
    192253      IF (.NOT. assigned_domain(ind)  .OR. .NOT. is_omp_level_master) CYCLE 
     
    209270       
    210271   ENDDO 
    211 !$OMP BARRIER 
    212 !$OMP MASTER 
    213    DEALLOCATE(field) 
    214 !$OMP END MASTER 
    215 !$OMP BARRIER 
    216         
    217   END SUBROUTINE deallocate_field 
     272  END SUBROUTINE deallocate_field_ 
    218273 
    219274  SUBROUTINE deallocate_field_glo(field) 
Note: See TracChangeset for help on using the changeset viewer.