
Hello, I wrote this code data DataFrameH5 a = DataFrameH5 (Nxs a) -- Nexus file (DataSource H5) -- gamma (DataSource H5) -- delta (DataSource H5) -- wavelength PoniGenerator -- ponie generator class Frame t a where len :: t -> IO (Maybe Int) row :: t -> Int -> MaybeT IO (DifTomoFrame a DIM1) instance Frame (DataFrameH5 DataFrameH5Path) DataFrameH5Path where len (DataFrameH5 _ _ (DataSourceH5 _ d) _ _) = lenH5Dataspace d row d@(DataFrameH5 nxs' g d' w ponigen) idx = do n <- lift $ len d let eof = fromJust n - 1 == idx let mu = 0.0 let komega = 0.0 let kappa = 0.0 let kphi = 0.0 gamma <- g `atIndex'` (ix1 0) delta <- d' `atIndex'` (ix1 idx) wavelength <- w `atIndex'` (ix1 0) let source = Source (head wavelength *~ nano meter) let positions = concat [mu, komega, kappa, kphi, gamma, delta] -- print positions let geometry = Geometry K6c source positions Nothing let detector = ZeroD m <- lift $ geometryDetectorRotationGet geometry detector poniext <- lift $ ponigen (MyMatrix HklB m) idx return $ DifTomoFrame { difTomoFrameNxs = nxs' , difTomoFrameIdx = idx , difTomoFrameEOF = eof , difTomoFrameGeometry = geometry , difTomoFramePoniExt = poniext } has you can see my t type contains also the a reference to the a one So when I create the instance, I need to write two times the DataFrameH5Path I would like to know how to write the same class with only class Frame t where len :: t -> IO (Maybe Int) row :: t -> Int -> MaybeT IO (DifTomoFrame <extract type a from type t> DIM1) thanks for your help Frederic

Maybe TypeFamilies would work for you? I can only give you a
barebones outline of what it might look like.
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-}
import Control.Monad.Trans.Maybe
data DataFrameH5 a = DataFrameH5
data DataFrameH5Path = DataFrameH5Path
class Frame t where
type Key t
len :: t -> IO (Maybe Int)
row :: t -> Int -> MaybeT IO (Key t)
instance Frame (DataFrameH5 a) where
type Key (DataFrameH5 a) = a
len DataFrameH5 = return . Just $ undefined
row DataFrameH5 idx = MaybeT $ do
return undefined
On Wed, Feb 22, 2017 at 10:27 AM, PICCA Frederic-Emmanuel
Hello, I wrote this code
data DataFrameH5 a = DataFrameH5 (Nxs a) -- Nexus file (DataSource H5) -- gamma (DataSource H5) -- delta (DataSource H5) -- wavelength PoniGenerator -- ponie generator
class Frame t a where len :: t -> IO (Maybe Int) row :: t -> Int -> MaybeT IO (DifTomoFrame a DIM1)
instance Frame (DataFrameH5 DataFrameH5Path) DataFrameH5Path where len (DataFrameH5 _ _ (DataSourceH5 _ d) _ _) = lenH5Dataspace d
row d@(DataFrameH5 nxs' g d' w ponigen) idx = do n <- lift $ len d let eof = fromJust n - 1 == idx let mu = 0.0 let komega = 0.0 let kappa = 0.0 let kphi = 0.0 gamma <- g `atIndex'` (ix1 0) delta <- d' `atIndex'` (ix1 idx) wavelength <- w `atIndex'` (ix1 0) let source = Source (head wavelength *~ nano meter) let positions = concat [mu, komega, kappa, kphi, gamma, delta] -- print positions let geometry = Geometry K6c source positions Nothing let detector = ZeroD m <- lift $ geometryDetectorRotationGet geometry detector poniext <- lift $ ponigen (MyMatrix HklB m) idx return $ DifTomoFrame { difTomoFrameNxs = nxs' , difTomoFrameIdx = idx , difTomoFrameEOF = eof , difTomoFrameGeometry = geometry , difTomoFramePoniExt = poniext }
has you can see my t type contains also the a reference to the a one So when I create the instance, I need to write two times the DataFrameH5Path
I would like to know how to write the same class with only
class Frame t where len :: t -> IO (Maybe Int) row :: t -> Int -> MaybeT IO (DifTomoFrame <extract type a from type t> DIM1)
thanks for your help
Frederic _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Hello thanks, I will investigate, but I like this solution. I can ad more type to a type family right ? Is it possible with this type family to be able to link in the other way ? a -> t Cheers Fred

It is hard to tell from your code what you intend, but it works
however you want it to, so long as it type checks.
class Frame a where
type Whatever a
len :: Whatever a -> IO (Maybe Int)
row :: Whatever a -> MaybeT IO (DifTomoFrame a DIM1)
instance Frame DataFrameH5Path where
type Whatever DataFrameH5Path = DataFrameH5
len = undefined -- :: DataFrameH5 -> IO (Maybe Int)
row = undefined -- :: DataFrameH5 -> Int -> MaybeT (DifTomoFrame
DataFrameH5Path DIM1)
On Wed, Feb 22, 2017 at 11:19 AM, PICCA Frederic-Emmanuel
Hello thanks, I will investigate, but I like this solution. I can ad more type to a type family right ?
Is it possible with this type family to be able to link in the other way ?
a -> t
Cheers
Fred _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

I should mention I just wrote that code off the cuff. It's probably
not even close to right. I recommend you mess with type families a
little to see if they get you where you want to go in your existing
code.
On Wed, Feb 22, 2017 at 11:29 AM, David McBride
It is hard to tell from your code what you intend, but it works however you want it to, so long as it type checks.
class Frame a where type Whatever a len :: Whatever a -> IO (Maybe Int) row :: Whatever a -> MaybeT IO (DifTomoFrame a DIM1)
instance Frame DataFrameH5Path where type Whatever DataFrameH5Path = DataFrameH5 len = undefined -- :: DataFrameH5 -> IO (Maybe Int) row = undefined -- :: DataFrameH5 -> Int -> MaybeT (DifTomoFrame DataFrameH5Path DIM1)
On Wed, Feb 22, 2017 at 11:19 AM, PICCA Frederic-Emmanuel
wrote: Hello thanks, I will investigate, but I like this solution. I can ad more type to a type family right ?
Is it possible with this type family to be able to link in the other way ?
a -> t
Cheers
Fred _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Hello, I am affected by this error src/Hkl/Xrd/OneD.hs:238:49-52: Could not deduce (Key a ~ Key b0) from the context (Frame a) bound by the type signature for getPoniExtRef :: Frame a => XRDRef (Key a) -> IO PoniExt at src/Hkl/Xrd/OneD.hs:235:18-56 NB: `Key' is a type function, and may not be injective The type variable `b0' is ambiguous Possible fix: add a type signature that fixes these type variable(s) Expected type: Nxs (Key b0) Actual type: Nxs (Key a) In the second argument of `withDataFrameH5', namely nxs' In the first argument of `(>->)', namely `withDataFrameH5 h5file nxs' (gen output f) yield' In the first argument of `toListM', namely `(withDataFrameH5 h5file nxs' (gen output f) yield >-> hoist lift (frames' [idx]))' I looked at this http://stackoverflow.com/questions/20870432/type-family-vs-data-family-in-br... So in your opinion it would be better to use a data family instead of a type familly ? Cheers

It is hard to tell from your code what you intend, but it works however you want it to, so long as it type checks.
class Frame a where type Whatever a len :: Whatever a -> IO (Maybe Int) row :: Whatever a -> MaybeT IO (DifTomoFrame a DIM1)
instance Frame DataFrameH5Path where type Whatever DataFrameH5Path = DataFrameH5 len = undefined -- :: DataFrameH5 -> IO (Maybe Int) row = undefined -- :: DataFrameH5 -> Int -> MaybeT (DifTomoFrame DataFrameH5Path DIM1)
In fact what I try realy to do is this. data DataFrameH5Path = DataFrameH5Path (DataItem H5) -- image (DataItem H5) -- gamma (DataItem H5) -- delta (DataItem H5) -- wavelength deriving (Show) data DataFrameH5 a = DataFrameH5 (Nxs a) -- Nexus file (DataSource H5) -- gamma (DataSource H5) -- delta (DataSource H5) -- wavelength PoniGenerator -- ponie generator withDataFrameH5 :: (Frame a, MonadSafe m) => File -> Nxs (Key a) -> PoniGenerator -> (a -> m r) -> m r withDataFrameH5 h nxs'@(Nxs _ _ (DataFrameH5Path _ g d w)) gen = bracket (liftIO before) (liftIO . after) where -- before :: File -> DataFrameH5Path -> m DataFrameH5 before :: IO a before = DataFrameH5 <$> return nxs' <*> openDataSource h g <*> openDataSource h d <*> openDataSource h w <*> return gen after :: a -> IO () after (DataFrameH5 _ g' d' w' _) = do closeDataSource g' closeDataSource d' closeDataSource w' I open and hdf5 file and I need to read a bunch of data from this file. the DataFrameH5 is a sort of resource like a File handler. I need a location in the file in order to acce the data, then I need to close the file So I store in the H5 type these resource, that I can release at the end. Ideally I would like to have only The H5Path type and hide the H5 one but I do not know how to do this. I have in fact different H5Path types which necessitate each time there corresponding H5 type. So I want a one for one relation between the H5 <-> H5Path type. Cheers Frederic
participants (2)
-
David McBride
-
PICCA Frederic-Emmanuel