source: LMDZ6/trunk/libf/phymar/PHY_Atm_S0_INI.f90 @ 3006

Last change on this file since 3006 was 2089, checked in by Laurent Fairhead, 10 years ago

Inclusion de la physique de MAR


Integration of MAR physics

File size: 5.6 KB
Line 
1      subroutine PHY_Atm_S0_INI
2
3!------------------------------------------------------------------------------+
4!                                                         Sat 15-Jun-2013  MAR |
5!   MAR          PHY_Atm_S0_INI                                                |
6!     subroutine PHY_Atm_S0_INI initializes Insolation Computation             |
7!                                                                              |
8!     version 3.p.4.1 created by H. Gallee,               Thu 25-Apr-2013      |
9!           Last Modification by H. Gallee,               Sat 15-Jun-2013      |
10!                                                                              |
11!------------------------------------------------------------------------------+
12!                                                                              |
13!     REFER.:   Ch.  Tricot, personal communication                            |
14!     ^^^^^^^   M.F. Loutre, personal communication and thesis (1993)          |
15!                                                                              |
16!     INPUT :   Mon_TU, Day_TU        : Month and Day of the Year              |
17!     ^^^^^^^   HourTU, MinuTU, Sec_TU: Hour, Minute, and Second               |
18!               lon__r(kcolp) : Latitude                             [radians] |
19!               lat__h(kcolp) : Longitude                              [hours] |
20!                                                                              |
21!     OUTPUT:   rsunS0        : Insolation normal to Atmosphere Top (W/m2)     |
22!     ^^^^^^^   csz0S0        : Cosinus of the Zenithal Distance               |
23!                                                                              |
24!------------------------------------------------------------------------------+
25
26
27! Global Variables
28! ================
29
30      use Mod_Real
31      use Mod_PHY____dat
32      use Mod_PHY____grd
33      use Mod_PHY____kkl
34      use Mod_PHY_S0_ctr
35      use Mod_PHY_S0_dat
36      use Mod_PHY_S0_grd
37      use Mod_PHY_S0_kkl
38
39
40      IMPLICIT NONE
41
42
43
44
45! LOCAL VARIABLES
46! ===============
47
48      integer                                              ::  ikl    !
49      real(kind=real8)                                     ::  omenor !  Fall Line Azimuth                      [radian] INI
50
51
52
53
54! ALLOCATION
55! ==========
56
57!          ****************
58      CALL PHY_Atm_S0_ALLOC
59!          ****************
60
61
62! INITIALIZATION
63! ==============
64
65
66! Insolation Parameters (kBP is time in kyear BP, and is prescribed in Mod_PHY_S0_dat)
67! ---------------------
68
69        ecc    =    ecc_EO(kBP)                                         ! Earth Orbit Eccentricity                   [-]
70        perh   =    perhEO(kBP)                                         ! Longitude of Perihelion               [degree]
71        xob    =    xob_EO(kBP)                                         ! Obliquity                             [degree]
72
73        pirr   =    Dg2Rad / 3600.
74
75        xee    =      ecc  * ecc                                        ! Square    of Eccentricity                  [-]
76        xse    = sqrt(un_1 - xee)                                       ! Square Root (1-Ecc**2)                     [-]
77        xe3    =      xee  * ecc                                        !
78        xl     =      perh +  180.0                                     ! Longitude of Aphelion                 [degree]
79        xllp   =      xl   * Dg2Rad                                     ! Longitude of Aphelion                 [radian]
80        so     =  sin(xob  * Dg2Rad)                                    ! sinus     of Obliquity
81
82        xlam  =(ecc/2.0+ecc*xee/8.0)*(1.0    +xse)*sin(    xllp)       &! true long. sun for mean long. = 0     [radian]
83     &        -(xee/4.0            )*(0.5    +xse)*sin(2.0*xllp)       &!
84     &         +ecc*xee/8.0         *(1.0/3.0+xse)*sin(3.0*xllp)        !
85        xlam  = 2.0*xlam/Dg2Rad                                         ! true long. sun for mean long. = 0     [degree]
86
87        step   = 360.00 /Tyear                                          ! Advance on Earth Orbit in 1 day   [degree/day]
88
89
90
91
92! Initialisation of Slope effect on Insolation: Slope Azimuth
93! ===========================================================
94
95        IF         (FaceS0)                                         THEN
96
97          DO ikl=1,kcolp
98
99                    slopS0(ikl) =      cos(atan(slopAP(ikl)))           !  Cosine of Fall Line Angle
100
101            IF (abs(sloxAP(ikl)).gt.zer0)                           THEN
102                    omenor = atan(sloyAP(ikl) / sloxAP(ikl))            !  Fall Line Azimuth   (Upslope Direction)
103              IF   (sloxAP(ikl) .lt.zer0)                              &!
104     &              omenor =  omenor + piNmbr                           !
105
106              IF   (omenor.gt.         piNmbr)                         &!
107     &              omenor =  -2.0d0 * piNmbr + omenor                  !
108              IF   (omenor.lt.        -piNmbr)                         &!
109     &              omenor =   2.0d0 * piNmbr + omenor                  !
110
111            ELSE
112              IF   (sloyAP(ikl).gt.zer0) then
113                    omenor =   0.5d0 * piNmbr
114              ELSE
115                    omenor =   1.5d0 * piNmbr
116              END IF
117            END IF
118
119                    omenS0(ikl) =      omenor - piNmbr                  !  Fall Line Azimuth (Downslope Direction)
120                                                                        !                 (in MAR Reference Frame)
121                                                                        !              (positive counterclockwise)
122          END DO
123
124        END IF
125
126
127      return
128      end subroutine PHY_Atm_S0_INI
Note: See TracBrowser for help on using the repository browser.