[Haskell-beginners] How to link two Types
David McBride
toad3k at gmail.com
Wed Feb 22 15:59:38 UTC 2017
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
<frederic-emmanuel.picca at synchrotron-soleil.fr> wrote:
> 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 at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
More information about the Beginners
mailing list