2017年10月26日木曜日

スポーク長計算


https://github.com/index333/spcal

からソースがDLできます。

新バージョンは

https://github.com/index333/spcal2


各寸法の測り方は
https://www.sheldonbrown.com/spoke-length.html
を参考にしてください。

まずサンプルファイルを作っておきます。

426.0
45.0
37.3
45.0
20.7

次のスクリプトを実行します。

$ cat sample | runghc spcal.hs

import Graphics.UI.Gtk
import System.IO
import MySpinBox
import Round
import Control.Monad
readSample :: IO [Double]
readSample = do
r <- getContents
return $ map read $ lines r
rad d = ((2*pi)/360)*d
dig r = r / (yen/360)
yen = rad 360 :: Double
hosei = 2.4 / 2 :: Double
calLen a b d k h = sqrt ((a^2+b^2+d^2) - (2*a*b*(cos $ alfa h k))) - hosei
where alfa h k = rad (360 / h * k)
disp h a b c s = do
print $ s++"-side"
let l = map (\x -> calLen (a/2) (b/2) c x h) [0,2..8]
zipWithM (\x y -> do
putStr $ show x
putStr "cross="
putStr $ show $ round1 y
putStrLn "mm")
([0..4]::[Int])
l
print ()
main = do
a:b:c:d:e:[] <- readSample
print $ a:b:c:d:e:[]
initGUI
window <- windowNew
hbox <- hBoxNew False 0
vbox <- vBoxNew False 0
boxPackStart vbox hbox PackNatural 0
let names = ["スポーク穴数",
"erd(mm)",
"pcd(mm)",
"flange2center(mm)",
"pcd(mm)",
"flange2center(mm)"]
adjs <- mkAdjustments [(32, 20, 40 ,4,4),
(a,200, 700, 0.1,10),
(b,30, 100 ,1,1),
(c,10, 50, 0.1,1),
(d,30, 100 ,1,1),
(e,10, 50, 0.1,1)]
spins@s0:s1:s2:s3:s4:s5 <- myAddSpinButtons hbox names adjs
mapM_ ( `set` [spinButtonDigits := 0]) [s0,s2,s4]
update adjs
mapM (\x-> onValueChanged x (update adjs)) adjs
containerAdd window vbox
widgetShowAll window
window `on` unrealize $ end adjs
mainGUI
end adjs = do
l <- mapM (`get` adjustmentValue) adjs
mapM_ (\x -> hPutStrLn stderr $ show x) $ tail l
mainQuit
update adjs = do
h:a:b:c:d:e:_ <- mapM (`get` adjustmentValue) adjs
disp h a b c "left"
disp h a d e "right"
view raw spcal.hs hosted with ❤ by GitHub

MySpinBox モジュール
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
Round モジュールも必要です。

module Round where
roundN :: Int -> Double -> Double
roundN n d = fromIntegral (round (d * 10 ^ n)) / fromIntegral (10 ^ n)
round1,round2 :: Double -> Double
round1 = roundN 1
round2 = roundN 2
view raw Round.hs hosted with ❤ by GitHub
Failed to load module “canberra-gtk-module” のようなエラーメッセージがでるかも知れません。
無視してもかまいませんが
libcanberra-gtk-module
をインストールすると解消します。

sudo apt-get install libcanberra-gtk-module

スポーク長の計算式は








aはErdの2分の1、bはpcdの2分の1、dはフランジとセンター間の距離。 hはホール数、kは組数です。
Haskellでは

calLen a b d k h = sqrt ((a^2+b^2+d^2) - (2*a*b*(cos $ alfa h k))) 
     where alfa h k = rad (360 / h * k) 

この計算は同心円上の2点間の距離の問題に還元できます。このような計算は複素数で行うととても楽になります。

ハブ軸を原点に、交差する2本のスポークの交点を複素平面上の実数軸にあわせます。
(32ホール、6本組)

(見やすいように、ハブは実際より大きく描いています。)

スポークの両端をハブ側をA点,リム側をB点としますと

点Aの位相(実数軸との角度)はどの組み方でも 
360度➗(リムの穴数➗2) x (組数ー1)➗2
32ホール、6本組の場合、22.5度×2.5=56.25度
絶対値(原点までの距離)はハブのPCDの半分

点Bの位相は組み方に関係なく
 360度➗リムの穴数×(−1)
32ホール、6本組の場合、ー11.25度
絶対値はリムのERDの半分。
 これにハブの厚みとスポークの長さ表示方法を考慮して関数化すると

dist :: RealFloat a => Complex a -> Complex a -> a -> a
dist x y z = sqrt (l * l + z * z) where l = magnitude (x - y)
calLen a b d k h = dist x y d - hosei        
    where   x = mkPolar b (yen / (h / 2) * (k - 1) / 2)
                 y = mkPolar a (yen / h * (-1))
     yen = pi * 2

 どちらを使っても同じ結果になります。

なおラジアル組みの場合、簡易な計算で求められますが、
たまたま位相が一致する特殊なケースとして一般化できます。

Javaなどのオブジェクト指向言語ではデータをオブジェクトのまま保存します。

Haskellではdata型をShowして保存し、読み込んでReadすると元のdata型に戻してくれます。

このやり方で新しく書き換えました。

$ runghc menu.hs

もう一度ソースの置き場所を・・・

https://github.com/index333/spcal2

なおリムやハブのデータはテストのための仮データです。



同じような画面構成の小さなプログラムを復数書かなければいけないとき、継承が恋しくなる。

一応テストはしてますが他のサイトでも検算して下さい。

http://spoke.gzmapss.com/

が使いやすいです。



後記:

しばらくたってから実際に使ってみると、復数開くウインドウの閉じ方に難があることがわかりました。
(^_^;)

実用上は問題ないのですが・・・
Guiのプログラムを復数立ち上げるというのは独立したスレッドを生むことになるので制御がむつかしいケースが生じます。

気になる場合は、

runghc mkRim.hs
runghc selector.hs
runghc selectRim.hs
runghc selectHub.hs
runghc spcal.hs

のようなスクリプトを作ります。

0 件のコメント:

コメントを投稿

Haskell Process

Haskellの System.Processは便利ですが、問題もあります。 単一スレッドでの逐次処理を保証していない。(想像です。) 次のようなスクリプトを書いてみた。 --a.hs main = print [1..10] --t.hs import Sy...