Ignore:
Timestamp:
05/20/13 16:35:23 (11 years ago)
Author:
dubos
Message:

Schmidt transform in metric.f90

File:
1 edited

Legend:

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

    r146 r155  
    5252  INTEGER,PARAMETER :: vdown=5 
    5353  INTEGER,PARAMETER :: vrdown=6 
    54  
    5554   
    5655CONTAINS 
    57    
     56 
     57  SUBROUTINE remap_schmidt 
     58    USE spherical_geom_mod 
     59    USE ioipsl 
     60    IMPLICIT NONE 
     61    INTEGER :: nf,i,j 
     62    REAL(rstd) :: schmidt_factor, schmidt_lon, schmidt_lat 
     63 
     64    ! Schmidt transform parameters 
     65    schmidt_factor = 1. 
     66    CALL getin('schmidt_factor', schmidt_factor) 
     67    schmidt_factor =  schmidt_factor**2. 
     68     
     69    schmidt_lon = 0. 
     70    CALL getin('schmidt_lon', schmidt_lon) 
     71    schmidt_lon = schmidt_lon * pi/180. 
     72 
     73    schmidt_lat = 45. 
     74    CALL getin('schmidt_lat', schmidt_lat) 
     75    schmidt_lat = schmidt_lat * pi/180. 
     76 
     77    DO nf=1,nb_face 
     78       DO j=1,jjm_glo 
     79          DO i=1,iim_glo 
     80             CALL schmidt_transform(vertex_glo(i,j,nf)%xyz, schmidt_factor, schmidt_lon, schmidt_lat) 
     81          END DO 
     82       END DO 
     83    END DO 
     84  END SUBROUTINE remap_schmidt 
     85 
    5886  SUBROUTINE allocate_metric 
    5987  IMPLICIT NONE 
     
    830858!    CALL compute_face 
    831859    CALL compute_face_projection 
     860    CALL remap_schmidt 
     861 
    832862    CALL set_index 
    833863    CALL set_cell 
Note: See TracChangeset for help on using the changeset viewer.