Impedance -- Haskell routines for linear electronics calculations This is part of some self-study: - learning Haskell though over-orthogonalizing abstractions - rehashing some analog electronic circuit design theory Entry: Modeling impedances as functions Date: Tue Nov 30 13:35:31 EST 2010 Seems like a good idea at first, but the Num typeclass needs Eq. So we can't do this. A functional representation is too abstract. -- An impedance is a function of angular frequency to impedance. -- Impedances can be added or put in parallel. (//) a b = 1 / ( 1 / a + 1 / b) -- Define numeric type classes to work on functions. These are -- parametric in the number type that represents the data S a = S a deriving (Show, Eq) data Ohm a = Ohm a deriving (Show, Eq) data Impedance a = Impedance (S a -> Ohm a) deriving (Show,Eq) instance Num (Impedance a) where (+) = \x y -> x + y -- This won't work as we don't have Eq for functions So we need a concrete data type and an interpreter. Entry: `impedance' as evaluator Date: Tue Nov 30 16:17:24 EST 2010 data Circuit a = C a | L a | R a | Par [Circuit a] | Ser [Circuit a] deriving (Show,Eq) -- An impedance is a function of angular frequency to impedance. impedance :: (Fractional a, RealFloat a) => (Circuit a) -> (Complex a) -> (Complex a) impedance c s = z c where inv x = 1 / x sum xs = foldr (+) 0 xs z (R x) = x :+ 0 z (C x) = inv (s * (x :+ 0)) z (L x) = s * (x :+ 0) z (Ser cs) = sum (map z cs) z (Par cs) = inv (sum (map (inv . z) cs)) This works well. Note that the Circuit data type has a misleading name: it is not a circuit but a 2-terminal. Let's change. 2-terminals are interesting because they allow a tree representation which is due to the simple ways 2-terminals can be combined to form new 2-terminals. A two-terminal is a binary tree. For generic n-terminals this is no longer possible. ( Or is it? Maybe there lurks an interesting way to represent circuits as zipper trees? ) Another thing that's interesting is several forms of duality[1]. Two are interesting: current vs voltage (C <-> L duality), and the low vs. high frequency duality that relates s <-> 1/s. What I want is, starting from the circuit element representation, derive a rational function in s. This could use the C/L duality whenever an inverse shows up, i.e. express rational functions in terms of units: Ohms and Siemens. See next post. This might be interesting for circuit simplification, but it doesn't seem so great as a form in itself. What you really want is a bode plot or a pole/zero set. Another point is a virtual ground. Is it possible to represent that as a 2-terminal element? It's a 3-terminal.. Let's focus on the algebra of the 2-terminals first. [1] http://en.wikipedia.org/wiki/Duality_%28electrical_circuits%29 Entry: Rational functions Date: Tue Nov 30 18:15:37 EST 2010 - Impedance and Admittance as rational functions in mutual recursion. -- A slight asymmetry to simplify the representation: resistance is -- always expressed in Ohms instead of as a conductance Siemens. The -- conversion fromresistance to conductance is preformed in the `show' -- or other compilation. data Impedance a = ImpR a | ImpL a | ImpA (Admittance a) data Admittance a = AdmG a | AdmC a | AdmI (Impedance a) impedance :: (Fractional a) => CircuitElement a -> Impedance a admittance :: (Fractional a) => CircuitElement a -> Admittance a impedance = i where i (R x) = ImpR x i (L x) = ImpL x i c@(C x) = ImpA (admittance c) i (Ser (R x) (R y)) = i (R (x + y)) admittance = a where a (R x) = AdmG (1 / x) a (C x) = AdmC x a l@(L x) = AdmI (impedance l) This idea seems interesting but it requires more simplification, i.e. ordering of all the primitive elements according to type to reduce them. I don't see much use in this yet. Moreover, there is no generic algebraic way to get to an expressions of the poles and zeros, which is what would be really interesting. This has to be done numerically. Entry: Now what Date: Thu Dec 2 11:24:54 EST 2010 To summarize: - Basic 2-terminal algebra: 3 primitives, 2 compositions - 2-terminal -> frequency dependent impedance What is missing: - Symmetries, i.e. Par a b = Par b a - Par [] and Ser [] don't mean anything - Short + Open circuit What can be changed? - Par and Ser are now binary operations - Write 'ohms' and 'siemens' symmetrically - introduce R (Either a) to restore symmetry between resitance and conductance - fixed that: have 2 constructors: R and G - factor the data type into: scalar, reactive, composite Entry: Fully dual representation Date: Thu Dec 2 18:35:28 EST 2010 import Data.Complex -- Dual representation of 2-terminals (continued fraction). -- "Half" two-terminal: 2 primitive elements, one composition. data HTT a = Resistive a -- V = R I ; I = G V | Reactive a -- V = L dI/dt ; I = C dV/dt | Composite (TT a) (TT a) -- V1 + V2 (ser) ; I1 + I2 (par) deriving (Show, Eq) -- A two-terminal is a dualized HTT for current or voltage. data TT a = Primal (HTT a) -- keep duals | Dual (HTT a) -- flip duals deriving (Show, Eq) imp s = i where -- Perfrom operation primal or dual view. i (Primal x) = op x i (Dual x) = 1 / op x -- Perform operation for half two-terminal in current view. op (Resistive v) = v :+ 0 op (Reactive v) = s * (v :+ 0) op (Composite x y) = (i x) + (i y) Entry: dual.hs and impedance fractions Date: Sat Dec 4 11:23:25 EST 2010 Currently I have something like this: showImpedance = s where -- Switch to dual variable s v (Dual htt) = "1 / (" ++ (s (dual v) (Primal htt)) ++ ")" -- Stay in primal variable s v (Primal htt) = s' v htt s' Voltage (Resistive x) = (show x) ++ " R" s' Current (Resistive x) = (show x) ++ " G" s' Voltage (Reactive x) = (show x) ++ " sL" s' Current (Reactive x) = (show x) ++ " sC" s' v (Composite a b) = "(" ++ (s v a) ++ " + " ++ (s v b) ++ ")" Where we keep track of which side of the Voltage/Current duality we're on. Note that this is only necessary to label the numbers. Otherwise there is no ambiguitiy. So for impedance functions, these can be simply left out: interpretation is up to the user of the function to determine whether it's an impedance or an admittance. Cleaned up: -- Network construction in terms of dual representation needs to -- maintain the primal/dual state during construction, and a -- convention of what the primal variable is. data Variable = Voltage | Current dual Voltage = Current dual Current = Voltage -- An example "compiler" that maintains this state would be a print -- function that outputs units, and later a LaTeX output. -- The state that's pushed trough the tree is simply the units of the -- resistive and reactive components. texImpedance :: (Show a) => Variable -> (TT a) -> String texPrimitiveImpedance :: (Show a) => Variable -> (HTT a) -> String texPrimitiveImpedance v = s' (units v) where units Voltage = ("\\Omega", "H") units Current = ("S", "F") s' (u, _) (Resistive x) = (show x) ++ u s' (_, u) (Reactive x) = "s" ++ (show x) ++ u texImpedance = s where -- Switch to dual variable s v (Dual htt) = "\frac{1}{" ++ (s (dual v) (Primal htt)) ++ "}" -- Stay in primal variable s v (Primal htt) = s' v htt s' v (Composite a b) = (s v a) ++ " + " ++ (s v b) s' v a = texPrimitiveImpedance v a -- An example "compiler" that doesn't need to distinguish is a raw -- impedance/admittance computation. The user needs to know whether -- the TT is an impedance or admittance. ance :: (RealFloat a) => (Complex a) -> (TT a) -> (Complex a) ance s = a' where a' (Dual htt) = 1 / (a htt) a' (Primal htt) = a htt a (Resistive r) = r :+ 0 a (Reactive r) = (r :+ 0) * s a (Composite x y) = (a' x) + (a' y) Conclusion: keeping track of primal/dual is only necessary when elements are explicitly named. So what is really necessary is to build such a set of abstract constructors. Something like this: data Ance = Impedance | Admittance dual Impedance = Admittance dual Admittance = Impedance res Impedance r = (Primal (Resistive r)) res Admittance r = (Dual (Resistive r)) ind Impedance l = (Primal (Reactive l)) int Admittance l = (Dual (Reactive l)) cap Admittance c = (Primal (Reactive c)) cap Impedance c = (Dual (Reactive c)) However, what we want is bottom-up construction, while the representation is definitely top-down. How to solve that? Entry: Absolute <-> relative/dual rep Date: Sat Dec 4 12:42:45 EST 2010 -- Network construction in terms of absolute elements/compositions -- needs to maintain the primal/dual state during construction. data Ance a = Impedance (TT a) | Admittance (TT a) deriving (Show, Eq) -- Primitive reps res r = Impedance (Primal (Resistive r)) cnd g = Admittance (Primal (Resistive g)) ind l = Impedance (Primal (Reactive l)) cap c = Admittance (Primal (Reactive c)) -- Admittance / Impedance rep conversion imp (Admittance tt) = Impedance (dual tt) imp a = a adm (Impedance tt) = Admittance (dual tt) adm a = a -- Convert rep and project down to TT anceTT (Impedance tt) = tt anceTT (Admittance tt) = tt imp' = anceTT . imp adm' = anceTT . adm -- Primitive absolute 2-terminal operations ser a b = Impedance (Primal (Composite (imp' a) (imp' b))) par a b = Admittance (Primal (Composite (adm' a) (adm' b)))