POV-Ray : Newsgroups : povray.text.scene-files : Kens Function Collection Server Time
28 Jul 2024 18:26:13 EDT (-0400)
  Kens Function Collection (Message 1 to 8 of 8)  
From: Ken
Subject: Kens Function Collection
Date: 5 Jun 1999 02:07:12
Message: <3758BD21.B37E7FF5@pacbell.net>
Just a random sampling of equasions I have collected form various sources.
Accuracy of these equations are not gauranteed and may indeed be totaly
wrong so please don't shoot me if they do not work. There are also references
to graphic examples which I cannot provide for you. Sorry.

If anybody does play with these and produces working code I would appreciate
a copy of the working Pov example so I can fill out this collection as an
aid to others that may follow in your steps.


  The Triaxial tritorus is defined parametrically as 
  
  x = sin(u) (1+cos(v)) 
  y = sin(u+2 PI/3) (1+cos(v+2 PI/3)) 
  z = sin(u+4 PI/3) (1+cos(v+4 PI/3) 
  
  Where -PI <= u <= PI and -PI <= v <= PI 
  
  unknow if the following works -
  sin(x)(1+cos(x))sin(y+2 12/3)(1+cos(y+2 12/3))sin(z+4 12/3)(1+cos(z+4 12/3)
  
  ---------------------------------------------------------------------------

  A Clien Cycloid Shape

  x= cos(u/c)*cos(u/b)*(a+cos(v))+sin(u/b)*sin(v)*cos(v); 
  y= sin(u/c)*cos(u/b)*(a+cos(v))+sin(u/b)*sin(v)*cos(v); 

  z=-sin(u/b)*(a+cos(v))+cos(u/b)*sin(v)*cos(v); 

  Where: 0<=u<=2 b c PI and 0<=v<=4 PI 

  a=10;
  b=3;
  c=2;
  X=Cos[u/c]*Cos[u/b]*(a+Cos[v])+Sin[u/b]*Sin[v]*Cos[v];
  Y=Sin[u/c]*Cos[u/b]*(a+Cos[v])+Sin[u/b]*Sin[v]*Cos[v];
  Z=-Sin[u/b]*(a+Cos[v])+Cos[u/b]*Sin[v]*Cos[v];

  ParametricPlot3D[{X, Y, Z}, {u, 0, 2*b*c*Pi}, {v, 0, 4 Pi},
        PlotPoints -> {120,10}, Axes -> False, Boxed -> False,
                 ViewPoint->{5.265, -6.828, 2.580}];

  ---------------------------------------------------------------------------
  
  To apply a random scale to the x demension and correct for rand scale
  as object is translated.
  
  #declare R = seed(pi);
  
  #declare NextX = 0;
  #while( NextX < 20 )
    #delare Scale = 1+rand(R);
    box{0,1 scale Scale}
    translate <NextX,0,0>
    #declare NextX = NextX + Scale
  #end
  
  -----------------------------------------------------------------------------
  
  Multifaceted sphere equations
  
  The equations of the points on the surface of the sphere are 
  
  x = cos(theta) cos(phi)
  y = cos(theta) sin(phi)
  z = sin(theta) 
  
  where  -90 <= theta <= 90 
           0 <= phi   <= 360 
  
  To create a facet approximation, theta and phi are stepped in
  small angles between their respective  bounds. So if we take
  the angle step size to be dtheta and dphi, the four vertices
  of any facet correspond to

       (theta,phi)
     (theta+dtheta,phi)
     (theta+dtheta,phi+dphi) 
     (theta,phi+dphi) 



  void CreateUnitSphere(dtheta,dphi)
  int dtheta,dphi;
  {
     int n;
     int theta,phi;
     XYZ p[4];
  
     for (theta=-90;theta<=90-dtheta;theta+=dtheta) {
        for (phi=0;phi<=360-dphi;phi+=dphi) {
           n = 0;
           p[n].x = cos(theta*DTOR) * cos(phi*DTOR);
           p[n].y = cos(theta*DTOR) * sin(phi*DTOR);
           p[n].z = sin(theta*DTOR);
           n++;
           p[n].x = cos((theta+dtheta)*DTOR) * cos(phi*DTOR);
           p[n].y = cos((theta+dtheta)*DTOR) * sin(phi*DTOR);
           p[n].z = sin((theta+dtheta)*DTOR);
           n++;
           p[n].x = cos((theta+dtheta)*DTOR) * cos((phi+dphi)*DTOR);
           p[n].y = cos((theta+dtheta)*DTOR) * sin((phi+dphi)*DTOR);
           p[n].z = sin((theta+dtheta)*DTOR);
           n++;
           if (theta > -90 && theta < 90) {
              p[n].x = cos(theta*DTOR) * cos((phi+dphi)*DTOR);
              p[n].y = cos(theta*DTOR) * sin((phi+dphi)*DTOR);
              p[n].z = sin(theta*DTOR);
              n++;
           }
  
           /* Do something with the n vertex facet p */
  
         }
       }
    }
    
    --------------------------------------------------------------------
  
  
   This short note describes the parametric equations which give
   rise to an approximate model of a drop of water, for example, a
   tear drop.
  
   The equations as functions of longitute phi and lattitude theta are:
  
  x = 0.5 *(1-cos(8)) sin(8) cos(circle with verticle line through it)
  y = 0.5 *(1-cos(8)) sin(8) sin(circle with verticle line through it)
  z = cos(8)
  
    where 0 <= circ w/line tru/it  <= 2pi
    and 0   <= 8 <= pi


   When theta is 0 there is a discontinuity at the apex where 
   x = 0  y = 0  z = 1

  An implicit equation for the aforementioned tear drop is:

  1 - 4x^2 - 4y^2 - 2z + 2z^3 - z^4 = 0,

  or, it simplifies a bit as 4(x^2+y^2)=(1+z)(1-z)^3, which is a surface
  of revolution bounded by -1 <= z <= 1.  The POV command is:

  quartic{ <
  0, 0, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, 0, 0, 0,
  0, 0, 0, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, 0, 0,
  -1, 2, 0, -2, 1> }

  Sometimes, a parametric map involving trig functions can be converted
  to an algebraic implicit equation by using new variables:

  u=cos(t),
  v=sin(t),

  and introducing a new implicit relation:

  u^2+v^2=1.

  The idea is to make the parametric equations into polynomials, at the
  cost of increasing the number of variables and equations.  Then u and
  v can (sometimes) be eliminated from the system of polynomial
  equations to get an implicit equation in x,y,z.

  ---------------------------------------------------------------------

  Parametric function that mathmaticaly discribes a shape quite similar
  in appearence to a cork screw blade.

  v*cos(4*u), u, v*sin(4*u)

  <-PI/2,-1>, <PI/2, 1>     
 
  ---------------------------------------------------------------------

  Parametric function that mathmaticaly discribes a shape quite similar
  in appearence to a cylinder or truncated cone.

  sin(v), u, cos(v)

  <-1,-PI>, <1,PI> 

  ---------------------------------------------------------------------
 
  A goniometric function implicitly defined by the following mathmatical
  expression
  
  function_xy
 
  function cos(10*(sqrt(sqr(x)+sqr(y))))

  ---------------------------------------------------------------------

  6th order polnominal function describing a heart shaped surface

  cub(2*sqr(x)+sqr(y)+sqr(z)-1) - (0.1*sqr(x)+sqr(y))*cub(z)


  ---------------------------------------------------------------------

  A torus shape ?

  function{sqrt(sqr(sqrt(sqr(x)+sqr(z))-R0)+sqr(y)) -R1 }

  ---------------------------------------------------------------------

  
  ---------------------------------------------------------------------
  a different surface      
  cos(10*(sqrt(sqrt(x)+sqrt(y))))
  ---------------------------------------------------------------------


=========================

 Borromean rings are three interlinked rings such that no two rings are linked.
 In other words, the three rings cannot be separated and yet no two of them are
 linked. 

 It can be shown that there is no solution for flat rings, it can only be
 constructed by perturbing the rings in a third dimension. 

 The rings can be formed with various base geometries including rectangles
 and triangles as shown below. 

 --------------------

 One way (as shown below) to create the rings mathematically is with the
 following three parametric equations, one for each ring. 

           (cos(u)       , sin(u) + r   , cos(3u) / 3)
           (cos(u) + 0.5 , sin(u) - r/2 , cos(3u) / 3)
           (cos(u) - 0.5 , sin(u) - r/2 , cos(3u) / 3)

  Where u = 0 -> 2pi

  This is illustrated below for r = sqrt(3)/3, the radius of the spheres
  placed along the path is 0.2 
  ----------

  It is possible to make the rings out of elliptical rings, it does
  require 3 dimensions. The parametric equations for the three "rings"
  are 
  (     0     , r1 cos(u) , r2 sin(u) )
  ( r2 cos(u) ,     0     , r1 sin(u) )
  ( r1 cos(u) , r2 sin(u) ,     0     )

  Where u = 0 -> 2pi
 This is illustrated below for r1 = 2, r2 = 1, and the radius of
 the tubes = 0.2  
 --------
 And finally, using box geometry...
 --------

===========================

  The Kuen Surface

        2(cos(s)+s sin(s)) sin(t)
  x =   -------------------------
            1+ s^2sin(t)^2

        2(sin(s)-s cos(s)) sin(t)
  y =   -------------------------
            1+ s^sin(t)^2

        log(tan(t/2))+2    cos(t)
  z =   -------------------------
            1+ s^2sin(t)^2

=======================
  Maeder's Owl

Maeder's Minimal Surface 

     x =   v cos(u) - 0.5 v2 cos(2 u); 
     y = - v sin(u) - 0.5 v2 sin(2 u); 
     z = 4 v1.5 cos(3 u / 2) / 3; 

     0 <= u <= 4 PI and 0 <= v <= 1 


=========================
C source for Meader's Owl
=========================

#include "stdio.h"
#include "stdlib.h"
#include "math.h"
#include "paulslib.h"

int main(int argc,char **argv)
{
   int i,j,nu=100,nv=20;
   double u,v;
   XYZ p;
   COLOUR colour;
   COLOUR black = {0.0,0.0,0.0};

   printf("CMESH\n%d %d\n",n+1,n+1);
   for (i=0;i<=n;i++) {
      for (j=0;j<=n;j++) {

         u = i * 4 * PI / nu;
         v = j / (double)nv;

         p.x = v * cos(u) - 0.5 * v * v * cos(2 * u);
         p.y = - v * sin(u) - 0.5 * v * v * sin(2 * u);
         p.z = 4 * pow(v,1.5) * cos(1.5 * u) / 3;

         colour = GetColour(u,0.0,4*PI,4);
         printf("%g %g %g %g %g %g 0.5\n",p.x,p.y,p.z,
            colour.r,colour.g,colour.b);
      } } }


===========================
Mobius Strip

  The mobius stip is the simplest geometric shape which has only one
  surface and only one edge. It can be created by taking a strip of
  paper, giving it a half twist along its long axis, and then joining
 the two narrow ends together.

  The mobius strip in 3 dimensions can be represented parameterically   f(s,t) as
follows 

   \       /
  x |     |  cos(s)+t*cos(s/2)*cos(s)
     \   /
  y  | = |   sin(s)+t*cos(s/2)*sin(s)
     /   \
  z |     |         t*sin(s/2)
   /       \

 where s ranges typically from  0.0 to 2.0*pi
 and   t ranges typically from -0.4 to 0.4


===============================================


  Knot Equasions

  Knot 4
  There are a whole family of curves including knots which are
  formed by the equations:

  x = r * cos(phi) * cos(theta)
  y = r * cos(phi) * sin(theta)
  z = r * sin(phi)

  which are the equations for converting from polar to cartesian coordinates
  except that we make r, theta, phi a function of a parameter beta which ranges
  from 0 to pi.

  For the following

  r(beta) = 0.8 + 1.6 * sin(6 * beta)
  theta(beta) = 2 * beta
  phi(beta) = 0.6 * pi * sin(12 * beta) 

  Knot 5
  Using the same systems of equations as in knot 4, with

  r(beta) = 1.2 * 0.6 * sin(0.5 * pi + 6 * beta)
  theta(beta) = 4 * beta
  phi(beta) = 0.2 * pi * sin(6 * beta)


  ---------------------------------------------------------------


SUPERTOID

The supertoroid is a family of geometric primitives based on the torus. Let
     r0 the radius of the inner ring
     r1 the radius of the outer ring
as illustrated below 

  Where theta and phi range from 0 to 2pi. The equation for the supertoroid is
 the same as that for the torus except that the sin and cosine terms are raised
 to powers. 

          n1              n2
  x = cos  (u) (r0+r1 cos  (v)

          n1              n2
  y = sin  (u) (r0+r1 cos  (v)

             n2
  z = r1 sin  (v)


  It is different values of these powers which give rise to a family
 of 3D shapes all basically toroidal in shape. The value of n1 determines
 the shape of the torus ring, n2 determines the shape of the cross
  section of the ring. 

  Examples of the supertoroid generated for different values of n1 and
 n2 are shown below, of course, the legal values of n1 and n2 form a
 continuum of values from 0 to infinity (although there are representation
 issues near 0 and above 4). 


================================================

This last is the SUPERTOID object I believe converted from the above
equation to work with the isosurface patch. I seem to recall that it
does not work 100% as expected and may indeed contain critical errors.

/*
#macro Supertoroid(_Rj, _Rn, _E1, _E2)
  union
    {
      parametric
        {
          function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(v) ^ _E2) *  _Rn
          <0, 0>, <2 * pi, 2 * pi>
          <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
          <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
          accuracy .001
          rotate <90, 0, 0>
        }
      parametric
        {
          function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(v) ^ _E2) *  _Rn
          <0, 0>, <2 * pi, 2 * pi>
          <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
          <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
          accuracy .001
          rotate <90, 0, 0>
          rotate <0, 90, 0>
        }
      parametric
        {
          function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(v) ^ _E2) *  _Rn
          <0, 0>, <2 * pi, 2 * pi>
          <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
          <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
          accuracy .001
          rotate <90, 0, 0>
          rotate <0, 180, 0>
        }
      parametric
        {
          function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
                   (sin(v) ^ _E2) *  _Rn
          <0, 0>, <2 * pi, 2 * pi>
          <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
          <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
          accuracy .001
          rotate <90, 0, 0>
          rotate <0, 270, 0>
        }
    }
#end

// End POV code

//You call it like this:

// Begin POV code

object
  {
    Supertoroid(8, 3, 2, .5)
    texture
      {
        pigment { color Red }
        normal { dents 2 scale <.1, 3, .2> }
        finish { specular 1 roughness .002 }
      }
    rotate <-30. -30, 0>
  }

*/






-- 
Ken Tyler

mailto://tylereng@pacbell.net


Post a reply to this message

From: Bob Hughes
Subject: Re: Kens Function Collection
Date: 5 Jun 1999 03:43:01
Message: <3758D4EC.98029342@aol.com>
Well that should be more than an appetizer for those eager to use Super
Patch functions.
I take it "Clien" is actually Klien, perhaps? And you're really Cen T.?


Ken wrote:
> 
>   Just a random sampling of equasions I have collected form various sources.
> Accuracy of these equations are not gauranteed and may indeed be totaly
> wrong so please don't shoot me if they do not work. There are also references
> to graphic examples which I cannot provide for you. Sorry.
> 
> If anybody does play with these and produces working code I would appreciate
> a copy of the working Pov example so I can fill out this collection as an
> aid to others that may follow in your steps.
> 
>   The Triaxial tritorus is defined parametrically as
> 
>   x = sin(u) (1+cos(v))
>   y = sin(u+2 PI/3) (1+cos(v+2 PI/3))
>   z = sin(u+4 PI/3) (1+cos(v+4 PI/3)
> 
>   Where -PI <= u <= PI and -PI <= v <= PI
> 
>   unknow if the following works -
>   sin(x)(1+cos(x))sin(y+2 12/3)(1+cos(y+2 12/3))sin(z+4 12/3)(1+cos(z+4 12/3)
> 
>   ---------------------------------------------------------------------------
> 
>   A Clien Cycloid Shape
> 
>   x= cos(u/c)*cos(u/b)*(a+cos(v))+sin(u/b)*sin(v)*cos(v);
>   y= sin(u/c)*cos(u/b)*(a+cos(v))+sin(u/b)*sin(v)*cos(v);
> 
>   z=-sin(u/b)*(a+cos(v))+cos(u/b)*sin(v)*cos(v);
> 
>   Where: 0<=u<=2 b c PI and 0<=v<=4 PI
> 
>   a=10;
>   b=3;
>   c=2;
>   X=Cos[u/c]*Cos[u/b]*(a+Cos[v])+Sin[u/b]*Sin[v]*Cos[v];
>   Y=Sin[u/c]*Cos[u/b]*(a+Cos[v])+Sin[u/b]*Sin[v]*Cos[v];
>   Z=-Sin[u/b]*(a+Cos[v])+Cos[u/b]*Sin[v]*Cos[v];
> 
>   ParametricPlot3D[{X, Y, Z}, {u, 0, 2*b*c*Pi}, {v, 0, 4 Pi},
>         PlotPoints -> {120,10}, Axes -> False, Boxed -> False,
>                  ViewPoint->{5.265, -6.828, 2.580}];
> 
>   ---------------------------------------------------------------------------
> 
>   To apply a random scale to the x demension and correct for rand scale
>   as object is translated.
> 
>   #declare R = seed(pi);
> 
>   #declare NextX = 0;
>   #while( NextX < 20 )
>     #delare Scale = 1+rand(R);
>     box{0,1 scale Scale}
>     translate <NextX,0,0>
>     #declare NextX = NextX + Scale
>   #end
> 
>   -----------------------------------------------------------------------------
> 
>   Multifaceted sphere equations
> 
>   The equations of the points on the surface of the sphere are
> 
>   x = cos(theta) cos(phi)
>   y = cos(theta) sin(phi)
>   z = sin(theta)
> 
>   where  -90 <= theta <= 90
>            0 <= phi   <= 360
> 
>   To create a facet approximation, theta and phi are stepped in
>   small angles between their respective  bounds. So if we take
>   the angle step size to be dtheta and dphi, the four vertices
>   of any facet correspond to
> 
>        (theta,phi)
>      (theta+dtheta,phi)
>      (theta+dtheta,phi+dphi)
>      (theta,phi+dphi)
> 
>   void CreateUnitSphere(dtheta,dphi)
>   int dtheta,dphi;
>   {
>      int n;
>      int theta,phi;
>      XYZ p[4];
> 
>      for (theta=-90;theta<=90-dtheta;theta+=dtheta) {
>         for (phi=0;phi<=360-dphi;phi+=dphi) {
>            n = 0;
>            p[n].x = cos(theta*DTOR) * cos(phi*DTOR);
>            p[n].y = cos(theta*DTOR) * sin(phi*DTOR);
>            p[n].z = sin(theta*DTOR);
>            n++;
>            p[n].x = cos((theta+dtheta)*DTOR) * cos(phi*DTOR);
>            p[n].y = cos((theta+dtheta)*DTOR) * sin(phi*DTOR);
>            p[n].z = sin((theta+dtheta)*DTOR);
>            n++;
>            p[n].x = cos((theta+dtheta)*DTOR) * cos((phi+dphi)*DTOR);
>            p[n].y = cos((theta+dtheta)*DTOR) * sin((phi+dphi)*DTOR);
>            p[n].z = sin((theta+dtheta)*DTOR);
>            n++;
>            if (theta > -90 && theta < 90) {
>               p[n].x = cos(theta*DTOR) * cos((phi+dphi)*DTOR);
>               p[n].y = cos(theta*DTOR) * sin((phi+dphi)*DTOR);
>               p[n].z = sin(theta*DTOR);
>               n++;
>            }
> 
>            /* Do something with the n vertex facet p */
> 
>          }
>        }
>     }
> 
>     --------------------------------------------------------------------
> 
> 
>    This short note describes the parametric equations which give
>    rise to an approximate model of a drop of water, for example, a
>    tear drop.
> 
>    The equations as functions of longitute phi and lattitude theta are:
> 
>   x = 0.5 *(1-cos(8)) sin(8) cos(circle with verticle line through it)
>   y = 0.5 *(1-cos(8)) sin(8) sin(circle with verticle line through it)
>   z = cos(8)
> 
>     where 0 <= circ w/line tru/it  <= 2pi
>     and 0   <= 8 <= pi
> 
>    When theta is 0 there is a discontinuity at the apex where
>    x = 0  y = 0  z = 1
> 
>   An implicit equation for the aforementioned tear drop is:
> 
>   1 - 4x^2 - 4y^2 - 2z + 2z^3 - z^4 = 0,
> 
>   or, it simplifies a bit as 4(x^2+y^2)=(1+z)(1-z)^3, which is a surface
>   of revolution bounded by -1 <= z <= 1.  The POV command is:
> 
>   quartic{ <
>   0, 0, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, 0, 0, 0,
>   0, 0, 0, 0, 0, 0, 0, 0, 0, 0, -4, 0, 0, 0, 0,
>   -1, 2, 0, -2, 1> }
> 
>   Sometimes, a parametric map involving trig functions can be converted
>   to an algebraic implicit equation by using new variables:
> 
>   u=cos(t),
>   v=sin(t),
> 
>   and introducing a new implicit relation:
> 
>   u^2+v^2=1.
> 
>   The idea is to make the parametric equations into polynomials, at the
>   cost of increasing the number of variables and equations.  Then u and
>   v can (sometimes) be eliminated from the system of polynomial
>   equations to get an implicit equation in x,y,z.
> 
>   ---------------------------------------------------------------------
> 
>   Parametric function that mathmaticaly discribes a shape quite similar
>   in appearence to a cork screw blade.
> 
>   v*cos(4*u), u, v*sin(4*u)
> 
>   <-PI/2,-1>, <PI/2, 1>
> 
>   ---------------------------------------------------------------------
> 
>   Parametric function that mathmaticaly discribes a shape quite similar
>   in appearence to a cylinder or truncated cone.
> 
>   sin(v), u, cos(v)
> 
>   <-1,-PI>, <1,PI>
> 
>   ---------------------------------------------------------------------
> 
>   A goniometric function implicitly defined by the following mathmatical
>   expression
> 
>   function_xy
> 
>   function cos(10*(sqrt(sqr(x)+sqr(y))))
> 
>   ---------------------------------------------------------------------
> 
>   6th order polnominal function describing a heart shaped surface
> 
>   cub(2*sqr(x)+sqr(y)+sqr(z)-1) - (0.1*sqr(x)+sqr(y))*cub(z)
> 
>   ---------------------------------------------------------------------
> 
>   A torus shape ?
> 
>   function{sqrt(sqr(sqrt(sqr(x)+sqr(z))-R0)+sqr(y)) -R1 }
> 
>   ---------------------------------------------------------------------
> 
> 
>   ---------------------------------------------------------------------
>   a different surface
>   cos(10*(sqrt(sqrt(x)+sqrt(y))))
>   ---------------------------------------------------------------------
> 
> =========================
> 
>  Borromean rings are three interlinked rings such that no two rings are linked.
>  In other words, the three rings cannot be separated and yet no two of them are
>  linked.
> 
>  It can be shown that there is no solution for flat rings, it can only be
>  constructed by perturbing the rings in a third dimension.
> 
>  The rings can be formed with various base geometries including rectangles
>  and triangles as shown below.
> 
>  --------------------
> 
>  One way (as shown below) to create the rings mathematically is with the
>  following three parametric equations, one for each ring.
> 
>            (cos(u)       , sin(u) + r   , cos(3u) / 3)
>            (cos(u) + 0.5 , sin(u) - r/2 , cos(3u) / 3)
>            (cos(u) - 0.5 , sin(u) - r/2 , cos(3u) / 3)
> 
>   Where u = 0 -> 2pi
> 
>   This is illustrated below for r = sqrt(3)/3, the radius of the spheres
>   placed along the path is 0.2
>   ----------
> 
>   It is possible to make the rings out of elliptical rings, it does
>   require 3 dimensions. The parametric equations for the three "rings"
>   are
>   (     0     , r1 cos(u) , r2 sin(u) )
>   ( r2 cos(u) ,     0     , r1 sin(u) )
>   ( r1 cos(u) , r2 sin(u) ,     0     )
> 
>   Where u = 0 -> 2pi
>  This is illustrated below for r1 = 2, r2 = 1, and the radius of
>  the tubes = 0.2
>  --------
>  And finally, using box geometry...
>  --------
> 
> ===========================
> 
>   The Kuen Surface
> 
>         2(cos(s)+s sin(s)) sin(t)
>   x =   -------------------------
>             1+ s^2sin(t)^2
> 
>         2(sin(s)-s cos(s)) sin(t)
>   y =   -------------------------
>             1+ s^sin(t)^2
> 
>         log(tan(t/2))+2    cos(t)
>   z =   -------------------------
>             1+ s^2sin(t)^2
> 
> =======================
>   Maeder's Owl
> 
> Maeder's Minimal Surface
> 
>      x =   v cos(u) - 0.5 v2 cos(2 u);
>      y = - v sin(u) - 0.5 v2 sin(2 u);
>      z = 4 v1.5 cos(3 u / 2) / 3;
> 
>      0 <= u <= 4 PI and 0 <= v <= 1
> 
> =========================
> C source for Meader's Owl
> =========================
> 
> #include "stdio.h"
> #include "stdlib.h"
> #include "math.h"
> #include "paulslib.h"
> 
> int main(int argc,char **argv)
> {
>    int i,j,nu=100,nv=20;
>    double u,v;
>    XYZ p;
>    COLOUR colour;
>    COLOUR black = {0.0,0.0,0.0};
> 
>    printf("CMESH\n%d %d\n",n+1,n+1);
>    for (i=0;i<=n;i++) {
>       for (j=0;j<=n;j++) {
> 
>          u = i * 4 * PI / nu;
>          v = j / (double)nv;
> 
>          p.x = v * cos(u) - 0.5 * v * v * cos(2 * u);
>          p.y = - v * sin(u) - 0.5 * v * v * sin(2 * u);
>          p.z = 4 * pow(v,1.5) * cos(1.5 * u) / 3;
> 
>          colour = GetColour(u,0.0,4*PI,4);
>          printf("%g %g %g %g %g %g 0.5\n",p.x,p.y,p.z,
>             colour.r,colour.g,colour.b);
>       } } }
> 
> ===========================
> Mobius Strip
> 
>   The mobius stip is the simplest geometric shape which has only one
>   surface and only one edge. It can be created by taking a strip of
>   paper, giving it a half twist along its long axis, and then joining
>  the two narrow ends together.
> 
>   The mobius strip in 3 dimensions can be represented parameterically   f(s,t) as
follows
> 
>    \       /
>   x |     |  cos(s)+t*cos(s/2)*cos(s)
>      \   /
>   y  | = |   sin(s)+t*cos(s/2)*sin(s)
>      /   \
>   z |     |         t*sin(s/2)
>    /       \
> 
>  where s ranges typically from  0.0 to 2.0*pi
>  and   t ranges typically from -0.4 to 0.4
> 
> ===============================================
> 
>   Knot Equasions
> 
>   Knot 4
>   There are a whole family of curves including knots which are
>   formed by the equations:
> 
>   x = r * cos(phi) * cos(theta)
>   y = r * cos(phi) * sin(theta)
>   z = r * sin(phi)
> 
>   which are the equations for converting from polar to cartesian coordinates
>   except that we make r, theta, phi a function of a parameter beta which ranges
>   from 0 to pi.
> 
>   For the following
> 
>   r(beta) = 0.8 + 1.6 * sin(6 * beta)
>   theta(beta) = 2 * beta
>   phi(beta) = 0.6 * pi * sin(12 * beta)
> 
>   Knot 5
>   Using the same systems of equations as in knot 4, with
> 
>   r(beta) = 1.2 * 0.6 * sin(0.5 * pi + 6 * beta)
>   theta(beta) = 4 * beta
>   phi(beta) = 0.2 * pi * sin(6 * beta)
> 
>   ---------------------------------------------------------------
> 
> SUPERTOID
> 
> The supertoroid is a family of geometric primitives based on the torus. Let
>      r0 the radius of the inner ring
>      r1 the radius of the outer ring
> as illustrated below
> 
>   Where theta and phi range from 0 to 2pi. The equation for the supertoroid is
>  the same as that for the torus except that the sin and cosine terms are raised
>  to powers.
> 
>           n1              n2
>   x = cos  (u) (r0+r1 cos  (v)
> 
>           n1              n2
>   y = sin  (u) (r0+r1 cos  (v)
> 
>              n2
>   z = r1 sin  (v)
> 
>   It is different values of these powers which give rise to a family
>  of 3D shapes all basically toroidal in shape. The value of n1 determines
>  the shape of the torus ring, n2 determines the shape of the cross
>   section of the ring.
> 
>   Examples of the supertoroid generated for different values of n1 and
>  n2 are shown below, of course, the legal values of n1 and n2 form a
>  continuum of values from 0 to infinity (although there are representation
>  issues near 0 and above 4).
> 
> ================================================
> 
> This last is the SUPERTOID object I believe converted from the above
> equation to work with the isosurface patch. I seem to recall that it
> does not work 100% as expected and may indeed contain critical errors.
> 
> /*
> #macro Supertoroid(_Rj, _Rn, _E1, _E2)
>   union
>     {
>       parametric
>         {
>           function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(v) ^ _E2) *  _Rn
>           <0, 0>, <2 * pi, 2 * pi>
>           <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
>           <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
>           accuracy .001
>           rotate <90, 0, 0>
>         }
>       parametric
>         {
>           function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(v) ^ _E2) *  _Rn
>           <0, 0>, <2 * pi, 2 * pi>
>           <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
>           <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
>           accuracy .001
>           rotate <90, 0, 0>
>           rotate <0, 90, 0>
>         }
>       parametric
>         {
>           function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(v) ^ _E2) *  _Rn
>           <0, 0>, <2 * pi, 2 * pi>
>           <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
>           <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
>           accuracy .001
>           rotate <90, 0, 0>
>           rotate <0, 180, 0>
>         }
>       parametric
>         {
>           function (cos(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(u) ^ _E1) * (_Rj + _Rn * (cos(v) ^ _E2)),
>                    (sin(v) ^ _E2) *  _Rn
>           <0, 0>, <2 * pi, 2 * pi>
>           <-(_Rj + _Rn + .1), -(_Rj + _Rn + .1), -(_Rj +_Rn +.1)>,
>           <_Rj +_Rn + .1, _Rj + _Rn + .1, _Rj + _Rn + .1>
>           accuracy .001
>           rotate <90, 0, 0>
>           rotate <0, 270, 0>
>         }
>     }
> #end
> 
> // End POV code
> 
> //You call it like this:
> 
> // Begin POV code
> 
> object
>   {
>     Supertoroid(8, 3, 2, .5)
>     texture
>       {
>         pigment { color Red }
>         normal { dents 2 scale <.1, 3, .2> }
>         finish { specular 1 roughness .002 }
>       }
>     rotate <-30. -30, 0>
>   }
> 
> */
> 
> --
> Ken Tyler
> 
> mailto://tylereng@pacbell.net

-- 
 omniVERSE: beyond the universe
  http://members.aol.com/inversez/homepage.htm
 mailto://inversez@aol.com?Subject=PoV-News


Post a reply to this message

From: Ken
Subject: Re: Kens Function Collection
Date: 5 Jun 1999 04:23:16
Message: <3758DD06.2FF09016@pacbell.net>
Bob Hughes wrote:
> 
> Well that should be more than an appetizer for those eager to use Super
> Patch functions.
> I take it "Clien" is actually Klien, perhaps? And you're really Cen T.?

Pick, Pick, Pick, Pick, Pick, Pick, Pick, Pick, (stop for breath of air),
Pick, Pick, Pick, Pick, Pick, Pick, Pick, Pick, ...

-- 
Ken Tyler

mailto://tylereng@pacbell.net


Post a reply to this message

From: Ken
Subject: Re: Kens Function Collection
Date: 5 Jun 1999 04:31:01
Message: <3758DED6.653F1AE0@pacbell.net>
> ================================================
> 
> This last is the SUPERTOID object I believe converted from the above
> equation to work with the isosurface patch. I seem to recall that it
> does not work 100% as expected and may indeed contain critical errors.

  I forgot to mention that this last conversion I believe is credited to
Jerry Anning whose contribtions should not be ignored.

 Thank you.


-- 
Ken Tyler

mailto://tylereng@pacbell.net


Post a reply to this message

From: Jan Danielsson
Subject: Re: Kens Function Collection
Date: 5 Jun 1999 05:44:14
Message: <wnaqnavryffbasnyhaznvygryvnpbz.fcv2br0.pminews@news.povray.org>
>  Just a random sampling of equasions I have collected form various sources.
>Accuracy of these equations are not gauranteed and may indeed be totaly
>wrong so please don't shoot me if they do not work. There are also references
>to graphic examples which I cannot provide for you. Sorry.

[..erotic material left out..]

You've just made my weekend. :-)


 /j


Post a reply to this message

From: Ron Parker
Subject: Re: Kens Function Collection
Date: 7 Jun 1999 11:34:41
Message: <375be691@netplex.aussie.org>
On Sat, 05 Jun 1999 02:42:36 -0500, Bob Hughes wrote:
>Well that should be more than an appetizer for those eager to use Super
>Patch functions.
>I take it "Clien" is actually Klien, perhaps? And you're really Cen T.?

[400+ lines of quoted text excised]

Is it really that hard to use your delete key, Bob?


Post a reply to this message

From: Bob
Subject: Re: Kens Function Collection
Date: 7 Jun 1999 21:42:40
Message: <375C74F1.DBCDA98@aol.com>
Oops, sorry. I do that sometimes but not much in the habit of doing so. Thanks for
clueing me in on this one, atrocious waste of message space. However, it would be
Edit/Select All then Del, or a selective highlight + Del key.

> Is it really that hard to use your delete key, Bob?


Post a reply to this message

From: Matt Giwer
Subject: Re: Kens Function Collection
Date: 22 Jun 1999 00:12:10
Message: <376F0DB5.872A1D1F@giwersworld.org>
OR ... 	
http://www.mhri.edu.au/~pdb/geometry/


Post a reply to this message


Attachments:
Download 'us-ascii' (1 KB)

Copyright 2003-2023 Persistence of Vision Raytracer Pty. Ltd.