Skip to content
Snippets Groups Projects
create_surfaces.f90 48.1 KiB
Newer Older
  • Learn to ignore specific revisions
  • !     if (iproc == 0) write (*,*) 'y12mt: ',y12mt
    !     if (iproc == 0) write (*,*) 'y12mb: ',y12mb
    
    
         if (abs(theta1).gt.eps) then
             y2as=tan(pi/2.d0-theta1)
         else
             y2as=1.d0
         endif
         if (abs(theta2).gt.eps) then
             y2bs=tan(pi/2.d0-theta2)
         else
             y2bs=1.d0
         endif
    
    
    !     if (iproc == 0) write (*,*) 'y2as: ',y2as
    !     if (iproc == 0) write (*,*) 'y2bs: ',y2bs
    
         y2au=y2u+(y2rad*tan((theta1-theta2)/2.d0))*cos(theta1)
         if (abs(theta1).gt.eps) then
           y2al=y2u+(dz1/psi1s*y2as)+(y2rad*tan((theta1-theta2)/2.d0))*cos(theta1)
         else
           y2al=y2au
         endif
         y2bu=y2u-y2rad*tan((theta1-theta2)/2.d0)
    !     if (abs(theta2).gt.eps) then
    !       y2bl=y2u-(dz1/psi1s*y2as)-(y2rad*tan((theta1-theta2)/2.d0))
    !     else
           y2bl=y2bu
    !     endif
    
    ! SHOULD THE y12mb's BELOW BE sin(theta1)'s INSTEAD?????????
    
         x2aut=x2ut-(y2rad*tan((theta1-theta2)/2.d0))*y12mb
         if (abs(theta1).gt.eps) then
           x2alt=x2ut+(dz1/psi1s*(1.d0/y2as))-(y2rad*tan((theta1-theta2)/2.d0))*y12mb
         else
           x2alt=x2ut+dz1/psi1s-(y2rad*tan((theta1-theta2)/2.d0))*y12mb
         endif
         x2but=x2ut
         x2blt=x2lt
         x2aub=x2ub+(y2rad*tan((theta1-theta2)/2.d0))*y12mb
         if (abs(theta2).gt.eps) then
           x2alb=x2ub-(dz1/psi1s*(1.d0/y2as))+(y2rad*tan((theta1-theta2)/2.d0))*y12mb
         else
           x2alb=x2ub-dz1/psi1s+(y2rad*tan((theta1-theta2)/2.d0))*y12mb
         endif
         x2bub=x2ub
         x2blb=x2lb
    !     if (iproc == 0) write (*,*) 'y2au: ',y2au
    !     if (iproc == 0) write (*,*) 'y2al: ',y2al
    !     if (iproc == 0) write (*,*) 'y2bu: ',y2bu
    !     if (iproc == 0) write (*,*) 'y2bl: ',y2bl
    !     if (iproc == 0) write (*,*) 'x2aut: ',x2aut
    !     if (iproc == 0) write (*,*) 'x2alt: ',x2alt
    !     if (iproc == 0) write (*,*) 'x2but: ',x2but
    !     if (iproc == 0) write (*,*) 'x2blt: ',x2blt
    !     if (iproc == 0) write (*,*) 'x2aub: ',x2aub
    !     if (iproc == 0) write (*,*) 'x2alb: ',x2alb
    !     if (iproc == 0) write (*,*) 'x2bub: ',x2bub
    !     if (iproc == 0) write (*,*) 'x2blb: ',x2blb
    
         m1=(y2l-y1l)/(x2lb-x1lb)
         !bb1=(y1l+(dz1/psi1s)*y1s)-m1*(x1lb-(dz1/psi1s))
         bb1=y1l-m1*x1lb
         a1=-m1
         b1=1
         c1=-bb1
    
         m2=(y2u-y1u)/(x2ub-x1ub)
         bb2=y1u-m2*x1ub
         a2=-m2
         b2=1
         c2=-bb2
    
         m3=(y2u-y1u)/(x2ut-x1ut)
         bb3=y1u-m3*x1ut
         a3=-m3
         b3=1
         c3=-bb3
    
         m4=(y2l-y1l)/(x2lt-x1lt)
         bb4=(y1l+(dz1/psi1s)*y1s)-m4*(x1lt+dz1/psi1s)
         a4=-m4
         b4=1
         c4=-bb4
    
         do i=1,ns
           z(i)=sp01
           if (y(i).ge.-y0s*x(i)+(y0u+x0ub) .and. y(i).ge.y0s*x(i)+(y0u-x0ut)) then
             if (y(i).ge.y0l) then
               if (y(i).ge.y0l+(dz2/psi2s)) then
                 if (abs(dz4).gt.eps) then
                   if (dz4.gt.eps) then
                     z(i)=max(sp01-dz2-psi3s*(y(i)-(y0l+(dz2/psi2s))),sp13)
                   else
                     z(i)=min(sp01-dz2-psi3s*(y(i)-(y0l+(dz2/psi2s))),sp13)
                   endif
                 else
                   z(i)=sp13
                 endif
               else
                 z(i)=sp01-psi2s*(y(i)-y0l)
               endif
             elseif (y(i).ge.y0u) then
               z(i)=sp01+psi1s*(y0l-y(i))
             elseif (y(i).lt.y0u) then
               z(i)=sp02
             endif
           elseif (y(i).ge.-y1s*x(i)+(y1s*x1ub+y1u) .and. y(i).ge.y1s*x(i)+(-y1s*x1ut+y1u)) then
             if (x(i).lt.x1lb) then
               if (x(i).lt.x1lb-dz2/psi2s) then
                 if (abs(dz4).gt.eps) then
                   if (dz4.gt.eps) then
                     z(i)=max(sp01-dz2-psi3s*(x1ub-dz2/psi2s)-x(i),sp13)
                   else
                     z(i)=min(sp01-dz2-psi3s*(x1ub-dz2/psi2s)-x(i),sp13)
                   endif
                 else
                   z(i)=sp13
                 endif
               else
                 z(i)=sp01-psi2s*(x1lb-x(i))
               endif
             elseif (x(i).ge.x1lb .and. x(i).lt.x1ub) then
               z(i)=sp01+psi1s*(x(i)-x1lb)
             elseif (x(i).ge.x1ub .and. x(i).lt.x1ut) then
               z(i)=sp02
             elseif (x(i).ge.x1ut .and. x(i).lt.x1lt) then
               z(i)=sp01-psi1s*(x(i)-x1lt)
             else
               if (x(i).lt.x1lt+(dz2/psi2s)) then
                 z(i)=sp01-psi2s*(x(i)-x1lt)
               else
                 if (abs(dz4).gt.eps) then
                   if (dz4.gt.eps) then
                     z(i)=max(sp01-dz2-psi3s*(x(i)-x1lt),sp13)
                   else
                     z(i)=min(sp01-dz2-psi3s*(x(i)-x1lt),sp13)
                   endif
                 else
                   z(i)=sp13
                 endif
               endif
             endif
           elseif (y(i).ge.-y2as*x(i)+(y2as*x2aub+y2au) .and. y(i).ge.y2as*x(i)+(-y2as*x2aut+y2au)) then
    !       elseif (y(i).ge.-y2s*x(i)+(y2s*x2ub+y2u) .and. y(i).ge.y2s*x(i)+(-y2s*x2ut+y2u)) then
    !         z(i)=0.13d0
             if (y(i).ge.m1*x(i)+bb1) then
               dist=abs(a1*x(i)+b1*y(i)+c1)/sqrt(a1**2.d0+b1**2.d0)
               if (dist.lt.(dz2/psi2s)) then
                 z(i)=sp01-psi2s*dist
               else
                 if (abs(dz4).gt.eps) then
                   if (dz4.gt.eps) then
                     z(i)=max(sp01-dz2-psi3s*(dist-(dz2/psi2s)),sp13)
                   else
                     z(i)=min(sp01-dz2-psi3s*(dist-(dz2/psi2s)),sp13)
                   endif
                 else
                   z(i)=sp13
                 endif
               endif
             elseif (y(i).ge.m2*x(i)+bb2 .and. y(i).lt.m1*x(i)+bb1) then
               dist=abs(a1*x(i)+b1*y(i)+c1)/sqrt(a1**2.d0+b1**2.d0)
               z(i)=sp01+dist*psi1s
             elseif (y(i).lt.m2*x(i)+bb2 .and. y(i).lt.m3*x(i)+bb3) then
               z(i)=sp02
             elseif (y(i).ge.m3*x(i)+bb3 .and. y(i).lt.m4*x(i)+bb4) then
               dist=abs(a4*x(i)+b4*y(i)+c4)/sqrt(a4**2.d0+b4**2.d0)
               z(i)=sp01+dist*psi1s
             else
               dist=abs(a4*x(i)+b4*y(i)+c4)/sqrt(a4**2.d0+b4**2.d0)
               if (dist.lt.(dz2/psi2s)) then
                 z(i)=sp01-psi2s*dist
               else
                 if (abs(dz4).gt.eps) then
                   if (dz4.gt.eps) then
                     z(i)=max(sp01-dz2-psi3s*(dist-(dz2/psi2s)),sp13)
                   else
                     z(i)=min(sp01-dz2-psi3s*(dist-(dz2/psi2s)),sp13)
                   endif
                 else
                   z(i)=sp13
                 endif
               endif
             endif
           !elseif (y(i).ge.-y2as*x(i)+(y2as*x2aub+y2au) .and. y(i).ge.y2as*x(i)+(-y2as*x2aut+y2au)) then
           elseif (y(i).ge.y2bu) then
             dist=sqrt((x(i)-(x2bub+y2rad))**2.d0+(y(i)-y2bu)**2.d0)
             if (dist <= y2rad) then
               z(i)=sp02
             elseif (dist <= y2rad+dz1/psi1s) then
               z(i)=sp01+((y2rad+dz1/psi1s)-dist)*psi1s
             elseif (dist <= y2rad+dz1/psi1s+dz2/psi2s) then
               z(i)=sp01-psi2s*(dist-(y2rad+dz1/psi1s))
             else
               if (abs(dz4) > eps) then
                 if (dz4 > eps) then
                   z(i)=max(sp01-dz2-psi3s*((y2rad+dz1/psi1s+dz2/psi2s+dz3/psi3s)-dist),sp13)
                 else
                   z(i)=min(sp01-dz2-psi3s*((y2rad+dz1/psi1s+dz2/psi2s+dz3/psi3s)-dist),sp13)
                 endif
               else
                 z(i)=sp13
               endif
             endif
           elseif (x(i) < x2lb) then
             if (x(i) < x2lb-(dz2/psi2s)) then
               if (abs(dz4).gt.eps) then
                 if (dz4.gt.eps) then
                   z(i)=max(sp01-dz2-psi3s*(x2lb-(dz2/psi2s)-x(i)),sp13)
                 else
                   z(i)=min(sp01-dz2-psi3s*(x2lb-(dz2/psi2s)-x(i)),sp13)
                 endif
               else
                 z(i)=sp13
               endif
             else
               z(i)=sp01-psi2s*(x2lb-x(i))
             endif
           elseif (x(i).ge.x2lb .and. x(i).lt.x2ub) then
             z(i)=sp01+psi1s*(x(i)-x2lb)
           elseif (x(i).ge.x2ub .and. x(i).lt.x2ut) then
             z(i)=sp02
           elseif (x(i).ge.x2ut .and. x(i).lt.x2lt) then
             z(i)=sp01+psi1s*(x2lb-x(i))
           else
             if (x(i) > x2ut+(dz2/psi2s)) then
               if (abs(dz4).gt.eps) then
                 if (dz4.gt.eps) then
                   z(i)=max(sp01-dz2-psi3s*(x(i)-(x2ut+(dz2/psi2s))),sp13)
                 else
                   z(i)=min(sp01-dz2-psi3s*(x(i)-(x2ut+(dz2/psi2s))),sp13)
                 endif
               else
                 z(i)=sp13
               endif
             else
               z(i)=sp01-psi2s*(x(i)-x2lt)
             endif
           endif
         enddo
    
       
       case (15)
            ! sp01 is the z base level (z0)
            ! sp02 is the x position of the peak (x0)
            ! sp03 is the y position of the peak (y0)
            ! sp04 is the elevation of the peak above base level (h)
            ! sp05 is the x radius (distance from peak to base) (rx)
            ! sp06 is the y width (distance from base to base) (ry)
            !     negative values create a cylinder of length -ry
            ! sp07 is the angle of slope in x-direction at the base in degree (phi)
            !     note that for ry<rx the slope at the base will be steeper in y direction
            !     also ensure that rx > h/tan(phi)
            !     phi<0 creates a dome unscaled in z-direction (doesn't force angle)
    
            ! sp08 is a radial offset from the specified surface (for spherical shells)
    
    
            !spherical shells need sphere radius to calculate adjusted values for h, rx and ry
            !do loop again with new values
    
            !checking validity of input values
            a1=sp04/tan(sp07*pi/180.d0)
            if (sp05<=2.d0*a1) then
                if (iproc.eq.0) then
                    write(*,*) 'WARNING: overconstrained surface values, ignoring set angle phi'
                endif
                sp07=-1.d0
            endif
            
    
                !Radius of spere unscaled in z direction
    
                b1=sp05*(sp05-a1)/sqrt(sp05*(sp05-2.d0*a1))
    
                !scaling factor for z-direction
                c1 = sp04/(b1-sqrt(b1**2-sp05**2))
            else 
                !Radius of unscaled sphere cutting through (x0,z0+h) and (x0+xr,z0)
                b1=(sp04**2+sp05**2)/(2.d0*sp04)
                c1=1.d0
            endif
            !z-value of sphere center
            zx=sp01+sp04-b1*c1;
    
            !adjust radius for shell offset
            b1 = b1 + sp08/c1
    
    
                if (sp06>0.d0) then 
                     !distance from center + squeezing in y-direction
    
                     dist=sqrt((x(i)-sp02)**2+((y(i)-sp03)*2.d0*sp05/sp06)**2)
    
                     z(i)=max(sp01,zx+c1*sqrt(b1**2-dist**2))
    
                    !distance from center in x-direction
    
                    dist=abs((x(i)-sp02))
                    if (dist>sp05 .or. abs(y(i)-sp03)>(-0.53d0*sp06)) then
                    !outside rotating cylinder
                        z(i)=sp01
                    elseif (abs(y(i)-sp03)<(-0.5d0*sp06)) then
                    !inside rotating cylinder
                        z(i)=zx+c1*sqrt(b1**2-dist**2)
                    else
                    !transition zone (3% of wy on both sides)
                        z(i)= sp01-(abs(y(i)-sp03)+0.53e0*sp06)/(-0.03e0*sp06)*(zx+c1*sqrt(b1**2-dist**2)-sp01)
                    endif
                endif
            enddo
            
               
    
       case default
             call stop_run ('surface type not defined$')
    end select
    
    return
    end