2017年11月3日金曜日

pcd,歯底距離

チェーンリングのPCD(ピッチ・サークル・ダイアメーター)を計算します。
チェーンリングのPCDとはチェーン用ギヤにチェーンを巻きつけたときチェーンピンが形作る仮想円の直径のことです。
これは1辺の長さが12.7mmの正N角形に外接する円の直径の計算に還元できます。
(
クランクのPCDと区別するため、あちらはBCD(ボルト・サークル・ダイアメーター)と表現します
)
次に歯底距離を計算します。

--Ch.hs
module Ch (chlen,pitch) where
import Data.Complex
pitch = 12.7
p = pitch
chlen a b c = (l + f + r) * 2
where rf = pcr a
rr = pcr b
l' = rf - rr
l = sqrt(c ** 2 - l' ** 2)
th = atan (c / l')
sf = sirc a / 2
sr = sirc b / 2
f = sf * (pi - th) / pi
r = sr * th / pi
sirc = (p *)
rOfd = 7.8 / 2
yen = pi * 2
rd0 n | even n = (n,round (rd d))
| otherwise = (n,round (rd' d))
where d = fromIntegral n
rd n = pcd n - rOfd * 2
rd' n = let a = mkPolar m (pi/n/2)
b = mkPolar m pi
in dist a b
where m = pcr n-rOfd
dist a b = magnitude (a - b)
pcr n = d / sin t
where d = p / 2
t = pi / n
pcd n = pcr n * 2
view raw Ch.hs hosted with ❤ by GitHub
歯底距離を測ればチェーンリングの歯数がわかります。

$ ghci
Prelude> :l Ch.hs
[1 of 1] Compiling Ch               ( Ch.hs, interpreted )
Ok, modules loaded: Ch.
*Ch> rd0 43
(43,166)
*Ch> rd0 44
(44,170)

歯底距離が166mmであれば歯数は43T
歯底距離が170mmであれば歯数は44T

チェーリングのPCDとリヤスプロケットのPCDがわかれば、シングル・バイクのチェーン長が計算できます。

芯間距離(チェーンステイ長)405mm、前スプロケット歯数48Tそして後スプロケット歯数16Tの場合

*Ch> chlen 48 16 405
1226.491724535387
*Ch> it / p
96.57415153821945

97リンク。(半コマ使用時)
98リンク。(半コマ不使用時)

チェーン長計算は下図を参考にしてください。


SpinBoxで入力を楽に

初期データは「tmp]に

$ cat tmp
[48.0,16.0,405.0]



module MySpinBox where
import Graphics.UI.Gtk
import Control.Monad
mkAdjustment :: (Double, Double, Double, Double, Double) -> IO Adjustment
mkAdjustment (v,l,u,s,p) = adjustmentNew v l u s p 0
{-
:: Double value - the initial value.
-> Double lower - the minimum value.
-> Double upper - the maximum value.
-> Double stepIncrement - the step increment.
-> Double pageIncrement - the page increment.
-> Double pageSize - the page size.
-}
mkAdjustments :: [(Double, Double, Double, Double, Double)] ->
IO [Adjustment]
mkAdjustments = mapM mkAdjustment
myAddSpinButtons :: HBox -> [String] ->[Adjustment] -> IO [SpinButton]
myAddSpinButtons box names adjustments = do
zipWithM (\x y -> myAddSpinButton box x y) names adjustments
myAddSpinButton :: HBox -> String -> Adjustment -> IO SpinButton
myAddSpinButton box name adj = do
vbox <- vBoxNew False 0
boxPackStart box vbox PackRepel 0
label <- labelNew (Just name)
miscSetAlignment label 0.0 0.5
boxPackStart vbox label PackNatural 0
spinb <- spinButtonNew adj 10 1
boxPackStart vbox spinb PackGrow 0
return spinb
view raw MySpinBox.hs hosted with ❤ by GitHub
import System.FilePath.Posix
import MySpinBox
import Graphics.UI.Gtk
import Ch
fn = "tmp"
main = do
l <- readFile fn
let [a,b,c] = read l::[Double]
initGUI
window <- windowNew
hbox <- hBoxNew False 0
vbox <- vBoxNew False 0
boxPackStart vbox hbox PackNatural 0
let spmods = [(a, 30, 60 ,1 , 10),
(b, 10, 30, 1, 10),
(c, 100, 1000 ,1, 10)]
let names = ["大ギヤ(T)" ,"小ギヤ(T)","rc(mm)"]
adjs <- mkAdjustments spmods
spins <- myAddSpinButtons hbox names adjs
mapM_ (`set` [spinButtonDigits := 0]) spins
mapM_ (\x-> onValueChanged x (update adjs)) adjs
containerAdd window vbox
widgetShowAll window
window `on` unrealize $ end adjs
mainGUI
update adjs = do
a:b:c:_ <- mapM (`get` adjustmentValue) adjs
print a
print b
print c
print $ chlen a b c / pitch
end adjs = do
a:b:c:_ <- mapM (`get` adjustmentValue) adjs
writeFile fn $ show [a,b,c]
mainQuit
view raw chlen.hs hosted with ❤ by GitHub

スプロケを交換したときに
リヤアクスルが何ミリ移動するか計算します。
--chFrame.hs
import Graphics.UI.Gtk
import Ch
import MySpinBox
import System.Random
fn = "tmp"
main = do
l <- readFile fn
print l
let [a,b,c] = read l::[Double]
let cl = chlen a b c
initGUI
window <- windowNew
hbox <- hBoxNew False 0
containerAdd window hbox
let names = ["大ギヤ(T)","小ギヤ(T)"]
let spmods = [(a, 30, 60 ,1,10),(b, 10, 30, 1, 10)]
adjs <- mkAdjustments spmods
spins <- myAddSpinButtons hbox names adjs
mapM_ (`set` [spinButtonDigits := 0]) spins
mapM_ (\x-> onValueChanged x (update adjs c cl)) adjs
widgetShowAll window
window `on` unrealize $ end adjs c cl
mainGUI
f adjs c cl = do
[a,b] <- mapM (`get` adjustmentValue) adjs
r <- try (pf a b cl) (c-50,c+50)
return ([a,b],r)
update adjs c cl = do
([a,b],r) <- f adjs c cl
disp c r (a,b)
end adjs c cl = do
([a,b],r) <- f adjs c cl
writeFile fn $ show [a,b,fromIntegral (round r)]
mainQuit
rnd l h = randomRIO (l,h) :: IO Double
e = 0.001
try f (l,h)= do
if abs (h -l) < e
then return h
else do
r <- rnd l h
if f r
then try f (r,h)
else try f (l,r)
disp c x (a,b) = do
putStr "rc. "
putStr $ show $ round c
putStr " -> "
putStr $ show $ round x
putStr " mm. 差 = "
putStrLn $ show $ round $ x - c
putStr "Ratio = "
putStrLn $ show $ a/b
pf a b cl c = cl > ch
where ch = chlen a b c
view raw chFrame.hs hosted with ❤ by GitHub

0 件のコメント:

コメントを投稿

myPlayer

-- pipe.hs import System.Process import System.Environment main :: IO () a:_ IO [FilePath] randomize lst = do let c = length lst ...