--------------------------------------------------------------------------------
module Print where
import DC
import Circuit
import Numeric
import Maybe
-- TODO Clean up code below - Fernan
opPrint opdat = do putStrLn "\n title : operating point \n"
mapM putStrLn nodeLL
mapM putStrLn vsrcLL
putStrLn " ..\n end."
where nodeLL = map nodeL [0..((length n) - 1 )]
vsrcLL | length (snd l) == 0 = [" "]
| otherwise
= map vsrcL [0..((length (snd l)) - 1)]
nodeL i = showStr (" (" ++ show (n!!i) ++ ")") 10
++ showFF 12 ((fst l)!!i) ++ "v"
vsrcL i = showStr (" v(" ++ show (s!!i) ++ ")") 10
++ showFF 12 ((snd l)!!i) ++ "a"
l = splitAt (length n) (opvalue opdat)
n = tail (nNODE (opInfo opdat))
s = nSRC (opInfo opdat)
trPrint j trdat = do putStrLn "\n title : transient analysis \n"
putStrLn $ " " ++ label
mapM putStrLn tdat
putStrLn "\n end."
where label = showStr "n" 8 ++ foldr1 (++) (map head j)
head i = (showStr (show ((n ++ s)!!i)) 10)
++ "\t"
tdat = map rr [0..(length (trvalue trdat)) - 1]
rr i = " " ++ showStr (show i) 8
++ showStr ((foldr1 (++) (mm i))) 10
mm h = map (ll h) j
ll z b = showFF 9 ((pp z)!!b) ++ "\t"
pp i = (trvalue trdat)!!i
n = tail (nNODE (trInfo trdat))
s = nSRC (trInfo trdat)
---
showFF n i | abs i > 1.0e9 = showEFloat (Just 3) i ""
| otherwise = showFFloat (Just z) i ""
where h = length (showFFloat (Just n) i "")
z | h > n = n - (h - n)
| otherwise = n
showStr string n = string ++ pad
where pad = replicate (n - (length string)) ' '
|