[contrib][haskell] add the DataSource type
[hkl.git] / contrib / haskell / src / Hkl / Diffabs / Melle.hs
blobe81c8bba278f7f05e9398f726dc37d56f7b2dd0f
1 {-# LANGUAGE CPP #-}
2 {-# LANGUAGE OverloadedStrings #-}
4 module Hkl.Diffabs.Melle
5 ( melle ) where
7 -- import Control.Concurrent (setNumCapabilities)
8 -- import Control.Concurrent.Async (mapConcurrently)
9 -- import Data.Array.Repa (DIM1, ix1)
10 -- import Data.Char (toUpper)
11 -- import Numeric.LinearAlgebra (ident)
12 -- import System.FilePath ((</>))
13 -- import Text.Printf (printf)
15 -- import Prelude hiding (concat, lookup, readFile, writeFile)
17 -- import Hkl.MyMatrix
18 -- import Hkl.PyFAI.PoniExt
19 -- import Hkl.Types
20 import Hkl.XRD
21 -- import Hkl.XRD.Calibration
22 -- import Hkl.Detector
24 -- | Samples
26 -- project :: FilePath
27 -- project = "/nfs/ruche-diffabs/diffabs-users/99160066/"
29 -- published :: FilePath
30 -- published = project </> "published-data"
32 -- beamlineUpper :: Beamline -> String
33 -- beamlineUpper b = [Data.Char.toUpper x | x <- show b]
35 -- nxs :: FilePath -> NxEntry -> (NxEntry -> DataFrameH5Path) -> Nxs
36 -- nxs f e h = Nxs f e (h e)
38 -- nxs' :: FilePath -> NxEntry -> (NxEntry -> a) -> Nxs' a
39 -- nxs' f e h = Nxs' f e (h e)
41 -- h5path :: NxEntry -> DataFrameH5Path
42 -- h5path nxentry =
43 -- DataFrameH5Path { h5pImage = DataItem (nxentry </> image) StrictDims
44 -- , h5pGamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
45 -- , h5pDelta = DataItem (nxentry </> delta) ExtendDims
46 -- , h5pWavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
47 q-- }
48 -- where
49 -- beamline :: String
50 -- beamline = beamlineUpper Diffabs
52 -- image = "scan_data/data_53"
53 -- gamma = "d13-1-cx1__EX__DIF.1-GAMMA__#1/raw_value"
54 -- delta = "scan_data/actuator_1_1"
55 -- wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
57 -- sampleCalibration :: XRDCalibration
58 -- sampleCalibration = XRDCalibration { xrdCalibrationName = "calibration"
59 -- , xrdCalibrationOutputDir = published </> "calibration"
60 -- , xrdCalibrationEntries = entries
61 -- }
62 -- where
64 -- idxs :: [Int]
65 -- idxs = [3, 6, 9, 15, 18, 21, 24, 27, 30, 33, 36, 39, 43]
67 -- entry :: Int -> XRDCalibrationEntry
68 -- entry idx = XRDCalibrationEntryNxs
69 -- { xrdCalibrationEntryNxs'Nxs = nxs (published </> "calibration" </> "XRD18keV_26.nxs") "scan_26" h5path
70 -- , xrdCalibrationEntryNxs'Idx = idx
71 -- , xrdCalibrationEntryNxs'NptPath = published </> "calibration" </> printf "XRD18keV_26.nxs_%02d.npt" idx
72 -- }
74 -- entries :: [XRDCalibrationEntry]
75 -- entries = [ entry idx | idx <- idxs]
78 -- sampleRef :: XRDRef
79 -- sampleRef = XRDRef "reference"
80 -- (published </> "calibration")
81 -- (nxs (published </> "calibration" </> "XRD18keV_26.nxs") "scan_26" h5path)
82 -- 6 -- BEWARE only the 6th poni was generated with the right Xpad_flat geometry.
84 h5path' :: NxEntry -> DataFrameMeshH5Path
85 h5path' nxentry =
86 DataFrameMeshH5Path { dataFrameMeshH5Path'Image = DataItem (nxentry </> image) StrictDims
87 , dataFrameMeshH5Path'MeshX = DataItem (nxentry </> meshX) StrictDims
88 , dataFrameMeshH5Path'MeshY = DataItem (nxentry </> meshY) StrictDims
89 , dataFrameMeshH5Path'Gamma = DataItem (nxentry </> beamline </> gamma) ExtendDims
90 , dataFrameMeshH5Path'Delta = DataItem (nxentry </> beamline </> delta) ExtendDims
91 , dataFrameMeshH5Path'Wavelength = DataItem (nxentry </> beamline </> wavelength) StrictDims
93 where
94 beamline :: String
95 beamline = beamlineUpper Diffabs
97 image = "scan_data/data_58"
98 meshX = "scan_data/actuator_1_1"
99 meshY = "scan_data/actuator_2_1"
100 gamma = "D13-1-CX1__EX__DIF.1-GAMMA__#1/raw_value"
101 delta = "D13-1-CX1__EX__DIF.1-DELTA__#1/raw_value"
102 wavelength = "D13-1-C03__OP__MONO__#1/wavelength"
104 -- bins :: DIM1
105 -- bins = ix1 8000
107 -- multibins :: DIM1
108 -- multibins = ix1 25000
110 -- threshold :: Threshold
111 -- threshold = Threshold 800
113 melle29 :: XRDSample' DataFrameMeshH5Path
114 melle29 = XRDSample' "MELLE_29"
115 (published </> "MELLE_29")
116 [ XrdNxs' bins multibins threshold n | n <-
117 [ nxs' (project </> "2016" </> "Run2" </> "2016-03-28" </> "MELLE_29.nxs") "scan_29" h5path'
121 -- -- meshSample :: String
122 -- -- meshSample = project </> "2016" "Run2" "2016-03-28" "MELLE_29.nxs"
123 -- -- scan_29 scan_data actuator_1_1 actuator_2_1 data_58 (images)
125 -- -- | Main
127 melle :: IO ()
128 melle = do
129 let samples = [melle29]
130 print samples
131 return ()
133 -- p <- getPoniExtRef sampleRef
135 -- -- flip the ref poni in order to fit the reality
136 -- -- let poniextref = p
137 -- let poniextref = setPose p (MyMatrix HklB (ident 3))
138 -- -- let poniextref = setPose (Hkl.PyFAI.PoniExt.flip p) (MyMatrix HklB (ident 3))
140 -- -- full calibration
141 -- poniextref' <- calibrate sampleCalibration poniextref Xpad32
142 -- -- print p
143 -- print poniextref
144 -- print poniextref'
146 -- -- integrate each step of the scan
147 -- _ <- mapM_ (integrateMesh poniextref') samples
149 -- return ()