--- /dev/null
+# Wiring mache ich von links nach rechts !!!
+
+...IDENTIFICATION DIVISION
+...PROGRAM-ID FallingParticle
+...VERSION 20240225
+...COMMENT Calculate the deflection from the vertical caused by the Earth's rotation of a particle falling freely from rest from a height h.
+...COMMENT Differential Equations:
+...COMMENT    x''=-bz'+ay' # x-axis is along latitude,  directed to east
+...COMMENT    y''=-ax'     # y-axis is along longitude, directed to north
+...COMMENT    z''=-g+ax'   # z-axis is perpendicular to the surface of earth
+...COMMENT    g: gravitational acceleration = 9,81 m/s²
+...COMMENT    a: 2*omega*sin(phi)
+...COMMENT    b: 2*omega*cos(phi)
+...COMMENT    omega: rotation velocity of the earth = 2*pi/day
+...COMMENT    phi: Latitude of location (0-90°)
+...COMMENT    Initial Condition: z(0)=h
+...COMMENT The full solution requires 6 INTEGRATORs, Anabrid-THAT just has 5. The deflection to longitude (y) is neglegible and can be omitted (marked #*).
+...COMMENT It could also be solved in a separated algorithm omitting x.
+
+...ENVIRONMENT DIVISION
+...TIMEBASE 1ms
+
+...DATA DIVISION
+SET COEFFICIENT.1 TO AY # 2*2pi/day*sin(phi)
+SET COEFFICIENT.2 TO AX # = AY
+SET COEFFICIENT.3 TO B  # 2*2pi/day*cos(phi)
+SET COEFFICIENT.4 TO G  # gravitational acceleration = 9,81 m/s²
+SET COEFFICIENT.5 TO H  # height h
+SET OUTPUT.X TO x
+SET OUTPUT.Y TO y
+SET OUTPUT.Z TO z
+
+INITIALIZE H by -1 TO -h # same as COMPUTE -1 TIMES H TO -h
+INITIALIZE G by +1 TO g
+
+INTEGRATE 1*-bz',1*ay' TO -x' # Input is x''
+INTEGRATE -x' TO x
+
+INTEGRATE y'' TO -y'
+INTEGRATE -y' TO y   
+
+INTEGRATE z'' TO -z' 
+INTEGRATE -z', IC:-h, LIMIT:(z >= 0) TO z
+
+-x' * AX -> -ax'
+-ax' = y''
+-y' * AY -> -ay'
+INVERT -ay' TO ay'
+-z' * B -> -bz'
+ADD 1*-ax', 1*g TO -g+ax'
+-g+ax' = z''
+
+...OPERATION DIVISION
+...MODE REPEAT
+...OP-TIME 7,3ms
 
 output(x): 4a*mu
 
 # calculating y
-multiply (mu, mu) -> mu^2
+multiply mu, mu -> mu^2
 mu^2 * 4ay -> 4ay*mu^2
 isum 4a*mu^2 -> -2a*mu^2     # just serves to devide by 2 because we need 2a instead of 4a
   /2
-invert (-2a*mu^2) -> 2a*mu^2 
+invert -2a*mu^2 -> 2a*mu^2 
 output(y): 2a*mu^2
 
 # display mu, so the sinus
 
--- /dev/null
+# TP1 10.28 Masses hanging on springs
+# Two identical masses m are hanging on 2 springs with same spring constant D. The system is performing small oscillations around the equilibrium position.
+# m*s1'' + D*s1 + D*(s1-s2) = 0 => s1'' = D/m * (s2 - 2*s1) = D/m*s2 - D/m*s1 - D/m*s1
+# m*s2'' + D*(s2-s1) = 0        => s2'' = D/m * (s1 - s2) = D/m*s1 - D/m*s2
+
+coefficient(1): D/m_1 # D/m for s1
+coefficient(2): D/m_2 # D/m for s2, identical to D/m_1
+coefficient(3): -1 -> -s1_0 # initial position of s1
+coefficient(4): -1 -> -s2_0 # initial position of s2
+
+iintegrate D/m*s2, -D/m*s1, -D/m*s1 -> -s1' # input is s1''
+iintegrate -s1' -> s1
+   IC: -s1_0
+s1 * D/m_1 -> D/m*s1
+invert D/m*s1 -> -D/m*s1
+
+iintegrate D/m*s1, -D/m*s2 -> -s2' # input is s2''
+iintegrate -s2' -> s2
+   IC: -s2_0
+s2 * D/m_2 -> D/m*s2
+invert D/m*s2 -> -D/m*s2
+
+output(x): s1
+output(y): s2
 
--- /dev/null
+# TP1 10.29 Two Masses fixed to walls
+# Two equal masses m are connected to each other by a spring (spring constant D) and on either side to a fixed wall.
+
+# m*s1'' + 2D*s1 - D*s2 = 0 => s1'' = -D/m*s1 -D/m*s1 + D/m*s2
+# m*s2'' + 2D*s1 - D*s1 = 0 => s2'' = -D/m*s2 -D/m*s2 + D/m*s1
+
+coefficient(1): D/m_1 # D/m for s1
+coefficient(2): D/m_2 # D/m for s2, identical to D/m_1
+coefficient(3): -1 -> -s1_0 # initial position of s1
+coefficient(4): -1 -> -s2_0 # initial position of s2
+
+iintegrate -D/m*s1, -D/m*s1, D/m*s2 -> -s1' # input is s1''
+iintegrate -s1' -> s1
+   IC: -s1_0
+s1 * D/m_1 -> D/m*s1
+invert D/m*s1 -> -D/m*s1
+
+iintegrate -D/m*s2, -D/m*s2, D/m*s1 -> -s2' # input is s2''
+iintegrate -s2' -> s2
+   IC: -s2_0
+s2 * D/m_2 -> D/m*s2
+invert D/m*s2 -> -D/m*s2
+
+output(x): s1
+output(y): s2
 
--- /dev/null
+# TP1 10.30 Linear Molecule
+# In a linear molecule of symmetric construction of type A-B-A the atoms are harmonically coupled and are performing small oscillations around the equilibrium positions.
+
+# s1'' = -omega0^2*s1 + omega0^2*s2
+# s2'' = -my (-omega0^2*s1 + omega0^2*s2 + omega0^2*s2 - omega0^2*s3)
+# s3'' = omega0^2*s2 - omega0^2*s3
+
+# NB: all integrators have to run with 100 nF capacitance, i.e. SLOW mode
+
+coefficient(1): omega0^2_1 # omega0^2 for s1
+coefficient(2): omega0^2_2 # omega0^2 for s2 # same as omega0^2_1
+coefficient(3): omega0^2_3 # omega0^2 for s3 # same as omega0^2_1
+coefficient(4): my
+coefficient(5): -1 -> -s1_0 # initial position of s1
+coefficient(6): -1 -> -s3_0 # initial position of s3
+# initial positon of s2, the central mass, is set to 0
+
+iintegrate -omega0^2_1*s1, omega0^2_2*s2 -> -s1'   # input is s1''
+iintegrate -s1' -> s1
+   IC: -s1_0
+invert s1 -> -s1
+-s1 * omega0^2_1 -> -omega0^2_1*s1
+
+iintegrate -my*bracket -> -s2'   # input is s2''
+# the following integrator has to be built up manually as THAT only has 5 integrators and we need 6
+# iintegrate -s2' -> s2
+openamp -s2' -> s2
+  loopback: capacitor(100nF)
+s2 * omega0^2_2 -> omega0^2_2*s2
+isum -omega0^2_1*s1, omega0^2_2*s2, omega0^2_2*s2, -omega0^2_3*s3 -> -bracket
+-bracket * my -> -my*bracket
+
+iintegrate omega0^2_2*s2, -omega0^2_3*s3 -> -s3'   # input is s3''
+iintegrate -s3' -> s3
+  IC: -s3_0
+invert s3 -> -s3
+-s3 * omega0^2_3 -> -omega0^2_3*s3
+
+ output(x): s1
+ output(y): s2
+ output(z): s3
 
--- /dev/null
+# Solving partial differential equations by descretizing space
+# This is an adoption of the application note “alpaca_23” from Anabrid [https://analogparadigm.com/downloads/alpaca_23.pdf] 
+# THAT only has 5 integrators, thus we have to reduce the number of elements
+#
+# u_0 = delta_t 
+# u''_1 = u_0 - 2*u_1 + u_2 
+# u''_2 = u_1 - 2*u_2 + u_3 
+# u_3 = 0
+
+coefficient(1): f1 # fix to 0.2 to get 2 for the integration
+coefficient(2): f2 # fix to 0.2 to get 2 for the integration
+coefficient(5): 1 -> delta_t
+u_0 = delta_t
+coefficient(6): 0 -> u_3
+
+iintegrate u_0, 10*:-f1u_1, u_2 -> -u'_1 # input is u''_1
+iintegrate -u'_1 -> u_1
+invert u_1 -> -u_1
+-u_1 * f1 -> -f1u_1
+
+iintegrate u_1, 10*:-f2u_2, u_3 -> -u'_2 # input is u''_2
+iintegrate -u'_2 -> u_2
+invert u_2 -> -u_2
+-u_2 * f2 -> -f2u_2
+
+output(x): u_1
+output(y): u_2