MODULE geo2ocean !!====================================================================== !! *** MODULE geo2ocean *** !! Ocean mesh : ??? !!====================================================================== !! History : OPA ! 07-1996 (O. Marti) Original code !! NEMO 1.0 ! 02-2008 (G. Madec) F90: Free form !! 3.0 ! !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! repcmo : !! angle : !! geo2oce : !!---------------------------------------------------------------------- USE dom_oce ! mesh and scale factors USE phycst ! physical constants USE par_kind ! precision USE lbclnk IMPLICIT NONE PRIVATE PUBLIC rot_rep REAL(wp), DIMENSION(jpi,jpj) :: & gsint, gcost, & ! cos/sin between model grid lines and NP direction at T point gsinu, gcosu, & ! cos/sin between model grid lines and NP direction at U point gsinv, gcosv, & ! cos/sin between model grid lines and NP direction at V point gsinf, gcosf ! cos/sin between model grid lines and NP direction at F point LOGICAL :: lmust_init = .TRUE. !: used to initialize the cos/sin variables (se above) !! * Substitutions !!---------------------------------------------------------------------- !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008) !! $Id: geo2ocean.F90 1833 2010-04-13 17:44:52Z smasson $ !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE rot_rep ( pxin, pyin, cd_type, cdtodo, prot ) !!---------------------------------------------------------------------- !! *** ROUTINE rot_rep *** !! !! ** Purpose : Rotate the Repere: Change vector componantes between !! geographic grid <--> stretched coordinates grid. !! !! History : !! 9.2 ! 07-04 (S. Masson) !! (O. Marti ) Original code (repere and repcmo) !!---------------------------------------------------------------------- REAL(wp), DIMENSION(jpi,jpj), INTENT( IN ) :: pxin, pyin ! vector componantes CHARACTER(len=1), INTENT( IN ) :: cd_type ! define the nature of pt2d array grid-points CHARACTER(len=5), INTENT( IN ) :: cdtodo ! specify the work to do: !! ! 'en->i' east-north componantes to model i componante !! ! 'en->j' east-north componantes to model j componante !! ! 'ij->e' model i-j componantes to east componante !! ! 'ij->n' model i-j componantes to east componante REAL(wp), DIMENSION(jpi,jpj), INTENT(out) :: prot !!---------------------------------------------------------------------- ! Initialization of gsin* and gcos* at first call ! ----------------------------------------------- IF( lmust_init ) THEN CALL angle ! initialization of the transformation lmust_init = .FALSE. ENDIF SELECT CASE (cdtodo) CASE ('en->i') ! 'en->i' est-north componantes to model i componante SELECT CASE (cd_type) CASE ('T') ; prot(:,:) = pxin(:,:) * gcost(:,:) + pyin(:,:) * gsint(:,:) CASE ('U') ; prot(:,:) = pxin(:,:) * gcosu(:,:) + pyin(:,:) * gsinu(:,:) CASE ('V') ; prot(:,:) = pxin(:,:) * gcosv(:,:) + pyin(:,:) * gsinv(:,:) CASE ('F') ; prot(:,:) = pxin(:,:) * gcosf(:,:) + pyin(:,:) * gsinf(:,:) CASE DEFAULT ; STOP 'Only T, U, V and F grid points are coded' END SELECT CASE ('en->j') ! 'en->j' est-north componantes to model j componante SELECT CASE (cd_type) CASE ('T') ; prot(:,:) = pyin(:,:) * gcost(:,:) - pxin(:,:) * gsint(:,:) CASE ('U') ; prot(:,:) = pyin(:,:) * gcosu(:,:) - pxin(:,:) * gsinu(:,:) CASE ('V') ; prot(:,:) = pyin(:,:) * gcosv(:,:) - pxin(:,:) * gsinv(:,:) CASE ('F') ; prot(:,:) = pyin(:,:) * gcosf(:,:) - pxin(:,:) * gsinf(:,:) CASE DEFAULT ; STOP 'Only T, U, V and F grid points are coded' END SELECT CASE ('ij->e') ! 'ij->e' model i-j componantes to est componante SELECT CASE (cd_type) CASE ('T') ; prot(:,:) = pxin(:,:) * gcost(:,:) - pyin(:,:) * gsint(:,:) CASE ('U') ; prot(:,:) = pxin(:,:) * gcosu(:,:) - pyin(:,:) * gsinu(:,:) CASE ('V') ; prot(:,:) = pxin(:,:) * gcosv(:,:) - pyin(:,:) * gsinv(:,:) CASE ('F') ; prot(:,:) = pxin(:,:) * gcosf(:,:) - pyin(:,:) * gsinf(:,:) CASE DEFAULT ; STOP 'Only T, U, V and F grid points are coded' END SELECT CASE ('ij->n') ! 'ij->n' model i-j componantes to est componante SELECT CASE (cd_type) CASE ('T') ; prot(:,:) = pyin(:,:) * gcost(:,:) + pxin(:,:) * gsint(:,:) CASE ('U') ; prot(:,:) = pyin(:,:) * gcosu(:,:) + pxin(:,:) * gsinu(:,:) CASE ('V') ; prot(:,:) = pyin(:,:) * gcosv(:,:) + pxin(:,:) * gsinv(:,:) CASE ('F') ; prot(:,:) = pyin(:,:) * gcosf(:,:) + pxin(:,:) * gsinf(:,:) CASE DEFAULT ; STOP 'Only T, U, V and F grid points are coded' END SELECT CASE DEFAULT ; STOP 'rot_rep: Syntax Error in the definition of cdtodo' END SELECT END SUBROUTINE rot_rep SUBROUTINE angle !!---------------------------------------------------------------------- !! *** ROUTINE angle *** !! !! ** Purpose : Compute angles between model grid lines and the North direction !! !! ** Method : !! !! ** Action : Compute (gsint, gcost, gsinu, gcosu, gsinv, gcosv, gsinf, gcosf) arrays: !! sinus and cosinus of the angle between the north-south axe and the !! j-direction at t, u, v and f-points !! !! History : !! 7.0 ! 96-07 (O. Marti ) Original code !! 8.0 ! 98-06 (G. Madec ) !! 8.5 ! 98-06 (G. Madec ) Free form, F90 + opt. !! 9.2 ! 07-04 (S. Masson) Add T, F points and bugfix in cos lateral boundary !!---------------------------------------------------------------------- INTEGER :: ji, jj ! dummy loop indices !! REAL(wp) :: & zlam, zphi, & ! temporary scalars zlan, zphh, & ! " " zxnpt, zynpt, znnpt, & ! x,y components and norm of the vector: T point to North Pole zxnpu, zynpu, znnpu, & ! x,y components and norm of the vector: U point to North Pole zxnpv, zynpv, znnpv, & ! x,y components and norm of the vector: V point to North Pole zxnpf, zynpf, znnpf, & ! x,y components and norm of the vector: F point to North Pole zxvvt, zyvvt, znvvt, & ! x,y components and norm of the vector: between V points below and above a T point zxffu, zyffu, znffu, & ! x,y components and norm of the vector: between F points below and above a U point zxffv, zyffv, znffv, & ! x,y components and norm of the vector: between F points left and right a V point zxuuf, zyuuf, znuuf ! x,y components and norm of the vector: between U points below and above a F point !!---------------------------------------------------------------------- ! ============================= ! ! Compute the cosinus and sinus ! ! ============================= ! ! (computation done on the north stereographic polar plane) DO jj = 2, (jpj-1) !CDIR NOVERRCHK DO ji = 2, jpi ! vector opt. ! north pole direction & modulous (at t-point) zlam = glamt(ji,jj) zphi = gphit(ji,jj) zxnpt = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) zynpt = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) znnpt = zxnpt*zxnpt + zynpt*zynpt ! north pole direction & modulous (at u-point) zlam = glamu(ji,jj) zphi = gphiu(ji,jj) zxnpu = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) zynpu = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) znnpu = zxnpu*zxnpu + zynpu*zynpu ! north pole direction & modulous (at v-point) zlam = glamv(ji,jj) zphi = gphiv(ji,jj) zxnpv = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) zynpv = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) znnpv = zxnpv*zxnpv + zynpv*zynpv ! north pole direction & modulous (at f-point) zlam = glamf(ji,jj) zphi = gphif(ji,jj) zxnpf = 0. - 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) zynpf = 0. - 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) znnpf = zxnpf*zxnpf + zynpf*zynpf ! j-direction: v-point segment direction (around t-point) zlam = glamv(ji,jj ) zphi = gphiv(ji,jj ) zlan = glamv(ji,jj-1) zphh = gphiv(ji,jj-1) zxvvt = 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) zyvvt = 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) znvvt = SQRT( znnpt * ( zxvvt*zxvvt + zyvvt*zyvvt ) ) znvvt = MAX( znvvt, 1.e-14 ) ! j-direction: f-point segment direction (around u-point) zlam = glamf(ji,jj ) zphi = gphif(ji,jj ) zlan = glamf(ji,jj-1) zphh = gphif(ji,jj-1) zxffu = 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) zyffu = 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) znffu = SQRT( znnpu * ( zxffu*zxffu + zyffu*zyffu ) ) znffu = MAX( znffu, 1.e-14 ) ! i-direction: f-point segment direction (around v-point) zlam = glamf(ji ,jj) zphi = gphif(ji ,jj) zlan = glamf(ji-1,jj) zphh = gphif(ji-1,jj) zxffv = 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) zyffv = 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) znffv = SQRT( znnpv * ( zxffv*zxffv + zyffv*zyffv ) ) znffv = MAX( znffv, 1.e-14 ) ! j-direction: u-point segment direction (around f-point) zlam = glamu(ji,jj+1) zphi = gphiu(ji,jj+1) zlan = glamu(ji,jj ) zphh = gphiu(ji,jj ) zxuuf = 2. * COS( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * COS( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) zyuuf = 2. * SIN( rad*zlam ) * TAN( rpi/4. - rad*zphi/2. ) & & - 2. * SIN( rad*zlan ) * TAN( rpi/4. - rad*zphh/2. ) znuuf = SQRT( znnpf * ( zxuuf*zxuuf + zyuuf*zyuuf ) ) znuuf = MAX( znuuf, 1.e-14 ) ! cosinus and sinus using scalar and vectorial products gsint(ji,jj) = ( zxnpt*zyvvt - zynpt*zxvvt ) / znvvt gcost(ji,jj) = ( zxnpt*zxvvt + zynpt*zyvvt ) / znvvt gsinu(ji,jj) = ( zxnpu*zyffu - zynpu*zxffu ) / znffu gcosu(ji,jj) = ( zxnpu*zxffu + zynpu*zyffu ) / znffu gsinf(ji,jj) = ( zxnpf*zyuuf - zynpf*zxuuf ) / znuuf gcosf(ji,jj) = ( zxnpf*zxuuf + zynpf*zyuuf ) / znuuf ! (caution, rotation of 90 degres) gsinv(ji,jj) = ( zxnpv*zxffv + zynpv*zyffv ) / znffv gcosv(ji,jj) =-( zxnpv*zyffv - zynpv*zxffv ) / znffv END DO END DO ! =============== ! ! Geographic mesh ! ! =============== ! DO jj = 2, (jpj-1) DO ji = 2, jpi ! vector opt. IF( MOD( ABS( glamv(ji,jj) - glamv(ji,jj-1) ), 360. ) < 1.e-8 ) THEN gsint(ji,jj) = 0. gcost(ji,jj) = 1. ENDIF IF( MOD( ABS( glamf(ji,jj) - glamf(ji,jj-1) ), 360. ) < 1.e-8 ) THEN gsinu(ji,jj) = 0. gcosu(ji,jj) = 1. ENDIF IF( ABS( gphif(ji,jj) - gphif(ji-1,jj) ) < 1.e-8 ) THEN gsinv(ji,jj) = 0. gcosv(ji,jj) = 1. ENDIF IF( MOD( ABS( glamu(ji,jj) - glamu(ji,jj+1) ), 360. ) < 1.e-8 ) THEN gsinf(ji,jj) = 0. gcosf(ji,jj) = 1. ENDIF END DO END DO ! =========================== ! ! Lateral boundary conditions ! ! =========================== ! ! lateral boundary cond.: T-, U-, V-, F-pts, sgn CALL lbc_lnk( gcost, 'T', -1._wp ) ; CALL lbc_lnk( gsint, 'T', -1._wp ) CALL lbc_lnk( gcosu, 'U', -1._wp ) ; CALL lbc_lnk( gsinu, 'U', -1._wp ) CALL lbc_lnk( gcosv, 'V', -1._wp ) ; CALL lbc_lnk( gsinv, 'V', -1._wp ) CALL lbc_lnk( gcosf, 'F', -1._wp ) ; CALL lbc_lnk( gsinf, 'F', -1._wp ) END SUBROUTINE angle END MODULE geo2ocean