[contrib/haskell] XRF -> XRD
[hkl.git] / contrib / haskell / src / Hkl / Diffabs / Martinetto.hs
blob32b16a9b4345c58ce33858c0738d24e704423732
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE OverloadedStrings #-}
4 module Hkl.Diffabs.Martinetto
5 ( main_martinetto ) where
7 #if __GLASGOW_HASKELL__ < 710
8 import Control.Applicative ((<$>), (<*>))
9 #endif
10 import Control.Monad (forM_, forever)
11 import Control.Monad.IO.Class (liftIO)
12 import Control.Monad.Morph (hoist)
13 import Data.Attoparsec.Text
14 import Data.ByteString.Char8 (pack)
15 import Data.Char (toUpper)
16 import Data.Either
17 import Data.Text (Text, intercalate, pack)
18 import Data.Text.IO (readFile, writeFile)
19 import Data.Vector.Storable (concat, head)
20 import Hkl.C (geometryDetectorRotationGet)
21 import Hkl.H5 ( Dataset
22 , File
23 , closeDataset
24 , get_position
25 , lenH5Dataspace
26 , openDataset
27 , withH5File )
28 import Hkl.PyFAI
29 import Hkl.Types
30 import Numeric.Units.Dimensional.Prelude (meter, nano, (/~), (*~))
31 import System.Directory (createDirectoryIfMissing)
32 import System.FilePath ((</>), dropExtension, takeFileName, takeDirectory)
33 import Prelude hiding (concat, lookup, readFile, writeFile)
35 import Pipes (Consumer, Pipe, lift, (>->), runEffect, await, yield)
36 import Pipes.Prelude (toListM)
37 import Pipes.Safe (MonadSafe(..), runSafeT, bracket)
38 import Text.Printf (printf)
40 -- | Types
42 type NxEntry = String
43 type OutputBaseDir = FilePath
44 type PoniGenerator = MyMatrix Double -> Int -> IO PoniExt
45 type SampleName = String
47 data XRDRef = XRDRef SampleName OutputBaseDir Nxs Int
49 data XRDSample = XRDSample SampleName OutputBaseDir [Nxs]-- ^ nxss
51 data Nxs = Nxs FilePath NxEntry DataFrameH5Path deriving (Show)
53 data PoniExt = PoniExt Poni (MyMatrix Double) deriving (Show)
55 data DifTomoFrame =
56 DifTomoFrame { df_nxs :: Nxs -- ^ nexus of the current frame
57 , df_n :: Int -- ^ index of the current frame
58 , df_geometry :: Geometry -- ^ diffractometer geometry
59 , df_poniext :: PoniExt -- ^ the ref poniext
60 } deriving (Show)
62 class Frame t where
63 len :: t -> IO (Maybe Int)
64 row :: t -> Int -> IO DifTomoFrame
66 data DataFrameH5Path =
67 DataFrameH5Path { h5pImage :: DataItem
68 , h5pGamma :: DataItem
69 , h5pDelta :: DataItem
70 , h5pWavelength :: DataItem
71 } deriving (Show)
73 data DataFrameH5 =
74 DataFrameH5 { h5nxs :: Nxs
75 , h5gamma :: Dataset
76 , h5delta :: Dataset
77 , h5wavelength :: Dataset
78 , ponigen :: PoniGenerator
81 instance Frame DataFrameH5 where
82 len d = lenH5Dataspace (h5delta d)
84 row d idx = do
85 let nxs' = h5nxs d
86 let mu = 0.0
87 let komega = 0.0
88 let kappa = 0.0
89 let kphi = 0.0
90 gamma <- get_position (h5gamma d) 0
91 delta <- get_position (h5delta d) idx
92 wavelength <- get_position (h5wavelength d) 0
93 let source = Source (Data.Vector.Storable.head wavelength *~ nano meter)
94 let positions = concat [mu, komega, kappa, kphi, gamma, delta]
95 let geometry = Geometry K6c source positions Nothing
96 let detector = Detector DetectorType0D
97 m <- geometryDetectorRotationGet geometry detector
98 poniext <- ponigen d (MyMatrix HklB m) idx
99 return DifTomoFrame { df_nxs = nxs'
100 , df_n = idx
101 , df_geometry = geometry
102 , df_poniext = poniext
105 -- | Samples
107 -- project = "/nfs/ruche-diffabs/diffabs-users/99160066/"
108 -- project = "/home/experiences/instrumentation/picca/data/99160066"
109 project :: FilePath
110 project = "/home/picca/data/99160066"
112 published :: FilePath
113 published = project </> "published-data"
115 beamlineUpper :: Beamline -> String
116 beamlineUpper b = [toUpper x | x <- show b]
118 nxs :: FilePath -> NxEntry -> (NxEntry -> DataFrameH5Path ) -> Nxs
119 nxs f e h5path = Nxs f e (h5path e)
121 calibration :: XRDRef
122 calibration = XRDRef "calibration"
123 (published </> "calibration")
124 (nxs (published </> "calibration" </> "XRD18keV_26.nxs") "scan_26" h5path)
126 where
127 beamline :: String
128 beamline = beamlineUpper Diffabs
130 image = "scan_data/data_53"
131 gamma = "d13-1-cx1__EX__DIF.1-GAMMA__#1/raw_value"
132 delta = "scan_data/trajectory_1_1"
133 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
135 h5path :: NxEntry -> DataFrameH5Path
136 h5path nxentry =
137 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
138 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
139 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
140 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
143 n27t2 :: XRDSample
144 n27t2 = XRDSample "N27T2"
145 (published </> "N27T2")
146 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "N27T2_14.nxs") "scan_14" h5path
147 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "N27T2_17.nxs") "scan_17" h5path
149 where
150 beamline :: String
151 beamline = beamlineUpper Diffabs
153 image = "scan_data/data_53"
154 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
155 delta = "scan_data/trajectory_1_1"
156 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
158 h5path :: NxEntry -> DataFrameH5Path
159 h5path nxentry =
160 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
161 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
162 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
163 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
166 r34n1 :: XRDSample
167 r34n1 = XRDSample "R34N1"
168 (published </> "R34N1")
169 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R34N1_28.nxs") "scan_28" h5path
170 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R34N1_37.nxs") "scan_37" h5path
172 where
173 beamline :: String
174 beamline = beamlineUpper Diffabs
176 image = "scan_data/data_53"
177 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
178 delta = "scan_data/trajectory_1_1"
179 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
181 h5path :: NxEntry -> DataFrameH5Path
182 h5path nxentry =
183 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
184 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
185 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
186 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
189 r23 :: XRDSample
190 r23 = XRDSample "R23"
191 (published </> "R23")
192 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R23_6.nxs") "scan_6" h5path
193 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R23_12.nxs") "scan_12" h5path
195 where
196 beamline :: String
197 beamline = beamlineUpper Diffabs
199 image = "scan_data/data_53"
200 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
201 delta = "scan_data/trajectory_1_1"
202 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
204 h5path :: NxEntry -> DataFrameH5Path
205 h5path nxentry =
206 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
207 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
208 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
209 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
212 r18 :: XRDSample
213 r18 = XRDSample "R18"
214 (published </> "R18")
215 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R18_20.nxs") "scan_20" h5path
216 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R18_24.nxs") "scan_24" h5path
218 where
219 beamline :: String
220 beamline = beamlineUpper Diffabs
222 image = "scan_data/data_53"
223 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
224 delta = "scan_data/trajectory_1_1"
225 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
227 h5path :: NxEntry -> DataFrameH5Path
228 h5path nxentry =
229 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
230 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
231 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
232 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
235 a3 :: XRDSample
236 a3 = XRDSample "A3"
237 (published </> "A3")
238 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "A3_13.nxs") "scan_13" h5path
239 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "A3_14.nxs") "scan_14" h5path
240 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "A3_15.nxs") "scan_15" h5path
242 where
243 beamline :: String
244 beamline = beamlineUpper Diffabs
246 image = "scan_data/data_53"
247 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
248 delta = "scan_data/trajectory_1_1"
249 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
251 h5path :: NxEntry -> DataFrameH5Path
252 h5path nxentry =
253 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
254 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
255 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
256 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
259 a2 :: XRDSample
260 a2 = XRDSample "A2"
261 (published </> "A2")
262 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "A2_14.nxs") "scan_14" h5path
263 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "A2_17.nxs") "scan_17" h5path
265 where
266 beamline :: String
267 beamline = beamlineUpper Diffabs
269 image = "scan_data/data_53"
270 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
271 delta = "scan_data/trajectory_1_1"
272 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
274 h5path :: NxEntry -> DataFrameH5Path
275 h5path nxentry =
276 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
277 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
278 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
279 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
282 d2 :: XRDSample
283 d2 = XRDSample "D2"
284 (published </> "D2")
285 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "D2_16.nxs") "scan_16" h5path
286 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "D2_17.nxs") "scan_17" h5path
288 where
289 beamline :: String
290 beamline = beamlineUpper Diffabs
292 image = "scan_data/data_53"
293 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
294 delta = "scan_data/trajectory_1_1"
295 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
297 h5path :: NxEntry -> DataFrameH5Path
298 h5path nxentry =
299 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
300 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
301 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
302 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
305 d3 :: XRDSample
306 d3 = XRDSample "D3"
307 (published </> "D3")
308 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "D3_14.nxs") "scan_14" h5path
309 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "D3_15.nxs") "scan_15" h5path
311 where
312 beamline :: String
313 beamline = beamlineUpper Diffabs
315 image = "scan_data/data_53"
316 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
317 delta = "scan_data/trajectory_1_1"
318 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
320 h5path :: NxEntry -> DataFrameH5Path
321 h5path nxentry =
322 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
323 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
324 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
325 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
328 r11 :: XRDSample
329 r11 = XRDSample "R11"
330 (published </> "R11")
331 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R11_5.nxs") "scan_5" h5path
332 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R11_6.nxs") "scan_6" h5path
333 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "R11_7.nxs") "scan_7" h5path
335 where
336 beamline :: String
337 beamline = beamlineUpper Diffabs
339 image = "scan_data/data_53"
340 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
341 delta = "scan_data/trajectory_1_1"
342 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
344 h5path :: NxEntry -> DataFrameH5Path
345 h5path nxentry =
346 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
347 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
348 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
349 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
352 d16 :: XRDSample
353 d16 = XRDSample "D16"
354 (published </> "D16")
355 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "D16_12.nxs") "scan_12" h5path
356 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "D16_15.nxs") "scan_15" h5path
357 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "D16_17.nxs") "scan_17" h5path
359 where
360 beamline :: String
361 beamline = beamlineUpper Diffabs
363 image = "scan_data/data_53"
364 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
365 delta = "scan_data/trajectory_1_1"
366 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
368 h5path :: NxEntry -> DataFrameH5Path
369 h5path nxentry =
370 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
371 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
372 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
373 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
376 k9a2 :: XRDSample
377 k9a2 = XRDSample "K9A2"
378 (published </> "K9A2")
379 [ nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "K9A2_1_31.nxs") "scan_31" h5path
380 , nxs (project </> "2016" </> "Run2" </> "2016-03-27" </> "K9A2_1_32.nxs") "scan_32" h5path
382 where
383 beamline :: String
384 beamline = beamlineUpper Diffabs
386 image = "scan_data/data_53"
387 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
388 delta = "scan_data/trajectory_1_1"
389 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
391 h5path :: NxEntry -> DataFrameH5Path
392 h5path nxentry =
393 DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
394 , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
395 , h5pDelta = DataItem (nxentry </> delta) ExtendDims
396 , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
399 -- {-# ANN module "HLint: ignore Use camelCase" #-}
402 -- import Graphics.Rendering.Chart.Easy
403 -- import Graphics.Rendering.Chart.Backend.Diagrams
405 -- plotPonies :: FilePath -> [PoniEntry] -> IO ()
406 -- plotPonies f entries = toFile def f $ do
407 -- layout_title .= "Ponies"
408 -- setColors [opaque blue]
409 -- let values = map extract entries
410 -- plot (line "am" [values [0,(0.5)..400]])
411 -- -- plot (points "am points" (signal [0,7..400]))
412 -- where
413 -- extract (PoniEntry _ _ (Length poni1) _ _ _ _ _ _) = poni1
415 -- | Usual methods
418 poniFromFile :: FilePath -> IO Poni
419 poniFromFile filename = do
420 content <- readFile filename
421 return $ case parseOnly poniP content of
422 Left _ -> error $ "Can not parse the " ++ filename ++ " poni file"
423 Right poni -> poni
425 getPoniExtRef :: XRDRef -> IO PoniExt
426 getPoniExtRef (XRDRef _ output nxs'@(Nxs f _ _) idx) = do
427 poniExtRefs <- withH5File f $ \h5file ->
428 runSafeT $ toListM ( withDataFrameH5 h5file nxs' (gen output f) yield
429 >-> hoist lift (frames' [idx]))
430 return $ df_poniext (Prelude.head poniExtRefs)
431 where
432 gen :: FilePath -> FilePath -> MyMatrix Double -> Int -> IO PoniExt
433 gen root nxs'' m idx' = do
434 poni <- poniFromFile $ root </> scandir ++ printf "_%02d.poni" idx'
435 return $ PoniExt poni m
436 where
437 scandir = takeFileName nxs''
439 integrate :: PoniExt -> XRDSample -> IO ()
440 integrate ref (XRDSample _ output nxss) = mapM_ (integrate' ref output) nxss
442 integrate' :: PoniExt -> OutputBaseDir -> Nxs -> IO ()
443 integrate' ref output nxs'@(Nxs f _ _) = do
444 Prelude.print f
445 withH5File f $ \h5file ->
446 runSafeT $ runEffect $
447 withDataFrameH5 h5file nxs' (gen ref) yield
448 >-> hoist lift (frames
449 >-> savePonies (pgen output f)
450 >-> savePy 300)
451 where
452 gen :: PoniExt -> MyMatrix Double -> Int -> IO PoniExt
453 gen ref' m _idx = return $ computeNewPoni ref' m
455 pgen :: OutputBaseDir -> FilePath -> Int -> FilePath
456 pgen o nxs'' idx = o </> scandir </> scandir ++ printf "_%02d.poni" idx
457 where
458 scandir = (dropExtension . takeFileName) nxs''
460 computeNewPoni :: PoniExt -> MyMatrix Double -> PoniExt
461 computeNewPoni (PoniExt p1 mym1) mym2 = PoniExt p2 mym2
462 where
463 p2 = map rotate p1
465 rotate :: PoniEntry -> PoniEntry
466 rotate e = rotatePoniEntry e mym1 mym2
468 createPy :: Int -> (DifTomoFrame, FilePath) -> Text
469 createPy nb (f, poniFileName) =
470 intercalate "\n" $
471 map Data.Text.pack ["#!/bin/env python"
472 , ""
473 , "from h5py import File"
474 , "from pyFAI import load"
475 , ""
476 , "PONIFILE = " ++ show p
477 , "NEXUSFILE = " ++ show nxs'
478 , "IMAGEPATH = " ++ show i
479 , "IDX = " ++ show idx
480 , "N = " ++ show nb
481 , "OUTPUT = " ++ show out
482 , "WAVELENGTH = " ++ show (w /~ meter)
483 , ""
484 , "ai = load(PONIFILE)"
485 , "ai.wavelength = WAVELENGTH"
486 , "with File(NEXUSFILE) as f:"
487 , " img = f[IMAGEPATH][IDX]"
488 , " ai.integrate1d(img, N, filename=OUTPUT)"
490 where
491 p = takeFileName poniFileName
492 (Nxs nxs' _ h5path) = df_nxs f
493 (DataItem i _) = h5pImage h5path
494 idx = df_n f
495 out = (dropExtension . takeFileName) poniFileName ++ ".dat"
496 (Geometry _ (Source w) _ _) = df_geometry f
498 -- | Pipes
500 withDataFrameH5 :: (MonadSafe m) => File -> Nxs -> PoniGenerator -> (DataFrameH5 -> m r) -> m r
501 withDataFrameH5 h nxs'@(Nxs _ _ d) gen = Pipes.Safe.bracket (liftIO $ before) (liftIO . after)
502 where
503 -- before :: File -> DataFrameH5Path -> m DataFrameH5
504 before :: IO DataFrameH5
505 before = DataFrameH5
506 <$> return nxs'
507 <*> openDataset' h (h5pGamma d)
508 <*> openDataset' h (h5pDelta d)
509 <*> openDataset' h (h5pWavelength d)
510 <*> return gen
512 -- after :: DataFrameH5 -> IO ()
513 after d' = do
514 closeDataset (h5gamma d')
515 closeDataset (h5delta d')
516 closeDataset (h5wavelength d')
518 -- openDataset' :: File -> DataItem -> IO Dataset
519 openDataset' hid (DataItem name _) = openDataset hid (Data.ByteString.Char8.pack name) Nothing
521 savePonies :: (Int -> FilePath) -> Pipe DifTomoFrame (DifTomoFrame, FilePath) IO ()
522 savePonies g = forever $ do
523 f <- await
524 let filename = g (df_n f)
525 lift $ createDirectoryIfMissing True (takeDirectory filename)
526 lift $ writeFile filename (content (df_poniext f))
527 lift $ Prelude.print $ "--> " ++ filename
528 yield (f, filename)
529 where
530 content :: PoniExt -> Text
531 content (PoniExt poni _) = poniToText poni
533 savePy :: Int-> Consumer (DifTomoFrame, FilePath) IO ()
534 savePy n = forever $ do
535 f@(_, poniFileName) <- await
536 let directory = takeDirectory poniFileName
537 let pyFileName = dropExtension poniFileName ++ ".py"
538 lift $ createDirectoryIfMissing True directory
539 lift $ writeFile pyFileName (createPy n f)
540 lift $ Prelude.print $ "--> " ++ pyFileName
542 frames :: (Frame a) => Pipe a DifTomoFrame IO ()
543 frames = do
544 d <- await
545 (Just n) <- lift $ len d
546 forM_ [0..n-1] (\i -> do
547 f <- lift $ row d i
548 yield f)
550 frames' :: (Frame a) => [Int] -> Pipe a DifTomoFrame IO ()
551 frames' idxs = do
552 d <- await
553 forM_ idxs (\i -> do
554 f <- lift $ row d i
555 yield f)
557 -- | Main
559 main_martinetto :: IO ()
560 main_martinetto = do
561 -- lire le ou les ponis de référence ainsi que leur géométrie
562 -- associée.
564 let samples = [n27t2, r34n1, r23, r18, a2, a3, d2, d3, r11, d16, k9a2]
566 poniextref <- getPoniExtRef calibration
568 -- calculer et écrire pour chaque point d'un scan un poni correspondant à la bonne géométries.
570 mapM_ (integrate poniextref) samples
572 -- plotPoni "/tmp/*.poni" "/tmp/plot.txt"
574 -- créer le script python d'intégration multi géométrie
576 -- l'executer pour faire l'intégration.
578 -- plot de la figure. (script python ou autre ?)