New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 15540 for NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/FLO – NEMO

Ignore:
Timestamp:
2021-11-26T12:27:56+01:00 (3 years ago)
Author:
sparonuz
Message:

Mixed precision version, tested up to 30 years on ORCA2.

Location:
NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/FLO
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/FLO/flo4rk.F90

    r13237 r15540  
    2020 
    2121   !                                   ! RK4 and Lagrange interpolation coefficients 
    22    REAL(wp), DIMENSION (4) ::   tcoef1 = (/  1.0  ,  0.5  ,  0.5  ,  0.0  /)   !  
    23    REAL(wp), DIMENSION (4) ::   tcoef2 = (/  0.0  ,  0.5  ,  0.5  ,  1.0  /)   ! 
    24    REAL(wp), DIMENSION (4) ::   scoef2 = (/  1.0  ,  2.0  ,  2.0  ,  1.0  /)   ! 
    25    REAL(wp), DIMENSION (4) ::   rcoef  = (/-1./6. , 1./2. ,-1./2. , 1./6. /)   ! 
    26    REAL(wp), DIMENSION (3) ::   scoef1 = (/  0.5  ,  0.5  ,  1.0  /)           ! 
     22   REAL(dp), DIMENSION (4) ::   tcoef1 = (/  1.0  ,  0.5  ,  0.5  ,  0.0  /)   !  
     23   REAL(dp), DIMENSION (4) ::   tcoef2 = (/  0.0  ,  0.5  ,  0.5  ,  1.0  /)   ! 
     24   REAL(dp), DIMENSION (4) ::   scoef2 = (/  1.0  ,  2.0  ,  2.0  ,  1.0  /)   ! 
     25   REAL(dp), DIMENSION (4) ::   rcoef  = (/-1./6. , 1./2. ,-1./2. , 1./6. /)   ! 
     26   REAL(dp), DIMENSION (3) ::   scoef1 = (/  0.5  ,  0.5  ,  1.0  /)           ! 
    2727 
    2828#  include "domzgr_substitute.h90" 
     
    5252      INTEGER ::  ierror              ! error value 
    5353 
    54       REAL(wp), DIMENSION(jpnfl)   ::   zgifl , zgjfl , zgkfl    ! index RK  positions 
    55       REAL(wp), DIMENSION(jpnfl)   ::   zufl  , zvfl  , zwfl     ! interpolated velocity at the float position  
    56       REAL(wp), DIMENSION(jpnfl,4) ::   zrkxfl, zrkyfl, zrkzfl   ! RK coefficients 
     54      REAL(dp), DIMENSION(jpnfl)   ::   zgifl , zgjfl , zgkfl    ! index RK  positions 
     55      REAL(dp), DIMENSION(jpnfl)   ::   zufl  , zvfl  , zwfl     ! interpolated velocity at the float position  
     56      REAL(dp), DIMENSION(jpnfl,4) ::   zrkxfl, zrkyfl, zrkzfl   ! RK coefficients 
    5757      !!--------------------------------------------------------------------- 
    5858      ! 
     
    169169      !!---------------------------------------------------------------------- 
    170170      INTEGER                    , INTENT(in   ) ::   Kbb, Kmm           ! ocean time level indices 
    171       REAL(wp) , DIMENSION(jpnfl), INTENT(in   ) ::   pxt , pyt , pzt    ! position of the float 
    172       REAL(wp) , DIMENSION(jpnfl), INTENT(  out) ::   pufl, pvfl, pwfl   ! velocity at this position 
     171      REAL(dp) , DIMENSION(jpnfl), INTENT(in   ) ::   pxt , pyt , pzt    ! position of the float 
     172      REAL(dp) , DIMENSION(jpnfl), INTENT(  out) ::   pufl, pvfl, pwfl   ! velocity at this position 
    173173      INTEGER                    , INTENT(in   ) ::   ki                 ! 
    174174      !! 
    175175      INTEGER  ::   jfl, jind1, jind2, jind3   ! dummy loop indices 
    176       REAL(wp) ::   zsumu, zsumv, zsumw        ! local scalar 
     176      REAL(dp) ::   zsumu, zsumv, zsumw        ! local scalar 
    177177      INTEGER  , DIMENSION(jpnfl)       ::   iilu, ijlu, iklu   ! nearest neighbour INDEX-u 
    178178      INTEGER  , DIMENSION(jpnfl)       ::   iilv, ijlv, iklv   ! nearest neighbour INDEX-v 
     
    181181      INTEGER  , DIMENSION(jpnfl,4)     ::   iidv, ijdv, ikdv   ! 64 nearest neighbour INDEX-v 
    182182      INTEGER  , DIMENSION(jpnfl,4)     ::   iidw, ijdw, ikdw   ! 64 nearest neighbour INDEX-w 
    183       REAL(wp) , DIMENSION(jpnfl,4)     ::   zlagxu, zlagyu, zlagzu   ! Lagrange  coefficients 
    184       REAL(wp) , DIMENSION(jpnfl,4)     ::   zlagxv, zlagyv, zlagzv   !    -           - 
    185       REAL(wp) , DIMENSION(jpnfl,4)     ::   zlagxw, zlagyw, zlagzw   !    -           - 
    186       REAL(wp) , DIMENSION(jpnfl,4,4,4) ::   ztufl , ztvfl , ztwfl   ! velocity at choosen time step 
     183      REAL(dp) , DIMENSION(jpnfl,4)     ::   zlagxu, zlagyu, zlagzu   ! Lagrange  coefficients 
     184      REAL(dp) , DIMENSION(jpnfl,4)     ::   zlagxv, zlagyv, zlagzv   !    -           - 
     185      REAL(dp) , DIMENSION(jpnfl,4)     ::   zlagxw, zlagyw, zlagzw   !    -           - 
     186      REAL(dp) , DIMENSION(jpnfl,4,4,4) ::   ztufl , ztvfl , ztwfl   ! velocity at choosen time step 
    187187      !!--------------------------------------------------------------------- 
    188188  
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/FLO/flo_oce.F90

    r13558 r15540  
    2929   INTEGER , PUBLIC, ALLOCATABLE, DIMENSION(:) ::   nfloat    !: number to identify searcher group 
    3030 
    31    REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   flxx , flyy , flzz    !: long, lat, depth of float (decimal degree, m >0) 
    32    REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   tpifl, tpjfl, tpkfl   !: (i,j,k) indices of float position 
     31   REAL(dp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   flxx , flyy , flzz    !: long, lat, depth of float (decimal degree, m >0) 
     32   REAL(dp), PUBLIC, ALLOCATABLE, DIMENSION(:) ::   tpifl, tpjfl, tpkfl   !: (i,j,k) indices of float position 
    3333 
    34    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wb   !: vertical velocity at previous time step (m s-1). 
     34   REAL(dp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wb   !: vertical velocity at previous time step (m s-1). 
    3535    
    3636   !                                   !! * namelist namflo : langrangian floats * 
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/FLO/floblk.F90

    r14644 r15540  
    4949      INTEGER :: jfl              ! dummy loop arguments 
    5050      INTEGER :: ind, ifin, iloop 
    51       REAL(wp)   ::       & 
     51      REAL(dp)   ::       & 
    5252         zuinfl,zvinfl,zwinfl,      &     ! transport across the input face 
    5353         zuoutfl,zvoutfl,zwoutfl,   &     ! transport across the ouput face 
     
    5656         zind 
    5757 
    58       REAL(wp), DIMENSION ( 2 )  ::   zsurfx, zsurfy   ! surface of the face of the mesh 
     58      REAL(dp), DIMENSION ( 2 )  ::   zsurfx, zsurfy   ! surface of the face of the mesh 
    5959 
    6060      INTEGER  , DIMENSION ( jpnfl )  ::   iil, ijl, ikl                   ! index of nearest mesh 
     
    6262      INTEGER  , DIMENSION ( jpnfl )  ::   iiinfl, ijinfl, ikinfl          ! index of input mesh of the float. 
    6363      INTEGER  , DIMENSION ( jpnfl )  ::   iioutfl, ijoutfl, ikoutfl       ! index of output mesh of the float. 
    64       REAL(wp) , DIMENSION ( jpnfl )  ::   zgifl, zgjfl, zgkfl             ! position of floats, index on  
     64      REAL(dp) , DIMENSION ( jpnfl )  ::   zgifl, zgjfl, zgkfl             ! position of floats, index on  
    6565      !                                                                         ! velocity mesh. 
    66       REAL(wp) , DIMENSION ( jpnfl )  ::    ztxfl, ztyfl, ztzfl            ! time for a float to quit the mesh 
     66      REAL(dp) , DIMENSION ( jpnfl )  ::    ztxfl, ztyfl, ztzfl            ! time for a float to quit the mesh 
    6767      !                                                                         ! across one of the face x,y and z  
    68       REAL(wp) , DIMENSION ( jpnfl )  ::    zttfl                          ! time for a float to quit the mesh  
    69       REAL(wp) , DIMENSION ( jpnfl )  ::    zagefl                         ! time during which, trajectorie of  
     68      REAL(dp) , DIMENSION ( jpnfl )  ::    zttfl                          ! time for a float to quit the mesh  
     69      REAL(dp) , DIMENSION ( jpnfl )  ::    zagefl                         ! time during which, trajectorie of  
    7070      !                                                                         ! the float has been computed 
    71       REAL(wp) , DIMENSION ( jpnfl )  ::   zagenewfl                       ! new age of float after calculation  
     71      REAL(dp) , DIMENSION ( jpnfl )  ::   zagenewfl                       ! new age of float after calculation  
    7272      !                                                                         ! of new position 
    73       REAL(wp) , DIMENSION ( jpnfl )  ::   zufl, zvfl, zwfl                ! interpolated vel. at float position 
    74       REAL(wp) , DIMENSION ( jpnfl )  ::   zudfl, zvdfl, zwdfl             ! velocity diff input/output of mesh 
    75       REAL(wp) , DIMENSION ( jpnfl )  ::   zgidfl, zgjdfl, zgkdfl          ! direction index of float 
     73      REAL(dp) , DIMENSION ( jpnfl )  ::   zufl, zvfl, zwfl                ! interpolated vel. at float position 
     74      REAL(dp) , DIMENSION ( jpnfl )  ::   zudfl, zvdfl, zwdfl             ! velocity diff input/output of mesh 
     75      REAL(dp) , DIMENSION ( jpnfl )  ::   zgidfl, zgjdfl, zgkdfl          ! direction index of float 
    7676      !!--------------------------------------------------------------------- 
    7777 
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/FLO/flodom.F90

    r14654 r15540  
    3131   INTEGER , ALLOCATABLE, DIMENSION(:) ::   iimfl, ijmfl, ikmfl       ! index mesh of floats 
    3232   INTEGER , ALLOCATABLE, DIMENSION(:) ::   idomfl, ivtest, ihtest    !   -      
    33    REAL(wp), ALLOCATABLE, DIMENSION(:) ::   zgifl, zgjfl,  zgkfl      ! distances in indexes 
     33   REAL(dp), ALLOCATABLE, DIMENSION(:) ::   zgifl, zgjfl,  zgkfl      ! distances in indexes 
    3434 
    3535 
     
    137137      INTEGER           :: itrash         ! trash var for reading 
    138138      INTEGER           :: ifl            ! number of floats to read 
    139       REAL(wp)          :: zdxab, zdyad 
     139      REAL(dp)          :: zdxab, zdyad 
    140140      LOGICAL           :: llinmesh 
    141141      CHARACTER(len=80) :: cltmp 
     
    233233            !        A--------|-----D 
    234234            ! 
    235             zdxab = flo_dstnce( flxx(jfl), flyy(jfl), CASTWP(glamf(iimfl(jfl)-1,ijmfl(jfl)-1)), flyy(jfl) ) 
    236             zdyad = flo_dstnce( flxx(jfl), flyy(jfl), flxx(jfl), CASTWP(gphif(iimfl(jfl)-1,ijmfl(jfl)-1)) ) 
     235            zdxab = flo_dstnce( flxx(jfl), flyy(jfl), glamf(iimfl(jfl)-1,ijmfl(jfl)-1), flyy(jfl) ) 
     236            zdyad = flo_dstnce( flxx(jfl), flyy(jfl), flxx(jfl), gphif(iimfl(jfl)-1,ijmfl(jfl)-1) ) 
    237237 
    238238            ! Translation of this distances (in meter) in indexes 
     
    368368         pcx, pcy, pdx, pdy,    &     ! ??? 
    369369         ptx, pty                     ! ??? 
    370       REAL(wp),  INTENT(in)::   & 
     370      REAL(dp),  INTENT(in)::   & 
    371371         px, py                       ! longitude and latitude 
    372372      LOGICAL , INTENT(out) ::  ldinmesh            ! ??? 
     
    381381       
    382382      ! 4 semi plane defined by the 4 points and including the extrememity 
    383       zabpt = fsline(pax,pay,pbx,pby,CASTDP(px),CASTDP(py)) 
    384       zbcpt = fsline(pbx,pby,pcx,pcy,CASTDP(px),CASTDP(py)) 
    385       zcdpt = fsline(pcx,pcy,pdx,pdy,CASTDP(px),CASTDP(py)) 
    386       zdapt = fsline(pdx,pdy,pax,pay,CASTDP(px),CASTDP(py)) 
     383      zabpt = fsline(pax,pay,pbx,pby,px,py) 
     384      zbcpt = fsline(pbx,pby,pcx,pcy,px,py) 
     385      zcdpt = fsline(pcx,pcy,pdx,pdy,px,py) 
     386      zdapt = fsline(pdx,pdy,pax,pay,px,py) 
    387387        
    388388      ! We compare the semi plane T with the semi plane including the point 
     
    427427      !! ** Method  :  
    428428      !!---------------------------------------------------------------------- 
    429       REAL(wp), INTENT(in) ::   pla1, phi1, pla2, phi2   ! ??? 
    430       !! 
    431       REAL(wp) :: dly1, dly2, dlx1, dlx2, dlx, dls, dld, dpi 
    432       REAL(wp) :: flo_dstnce 
     429      REAL(dp), INTENT(in) ::   pla1, phi1, pla2, phi2   ! ??? 
     430      !! 
     431      REAL(dp) :: dly1, dly2, dlx1, dlx2, dlx, dls, dld, dpi 
     432      REAL(dp) :: flo_dstnce 
    433433      !!--------------------------------------------------------------------- 
    434434      ! 
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/FLO/flowri.F90

    r14644 r15540  
    3030   CHARACTER (len=80)  :: clname             ! netcdf output filename 
    3131 
    32    REAL(wp), ALLOCATABLE, DIMENSION(:) ::   zlon , zlat, zdep   ! 2D workspace 
    33    REAL(wp), ALLOCATABLE, DIMENSION(:) ::   ztem , zsal, zrho   ! 2D workspace 
     32   REAL(dp), ALLOCATABLE, DIMENSION(:) ::   zlon , zlat, zdep   ! 2D workspace 
     33   REAL(dp), ALLOCATABLE, DIMENSION(:) ::   ztem , zsal, zrho   ! 2D workspace 
    3434 
    3535   !!---------------------------------------------------------------------- 
     
    7373      INTEGER  :: irec, irecflo 
    7474 
    75       REAL(wp) :: zafl,zbfl,zcfl                 ! temporary real 
    76       REAL(wp) :: ztime                          !   " 
     75      REAL(dp) :: zafl,zbfl,zcfl                 ! temporary real 
     76      REAL(dp) :: ztime                          !   " 
    7777 
    7878      INTEGER, DIMENSION(2)          :: icount 
Note: See TracChangeset for help on using the changeset viewer.