[Haskell-cafe] HKD and Generic

PICCA Frederic-Emmanuel frederic-emmanuel.picca at synchrotron-soleil.fr
Thu Feb 9 13:11:00 UTC 2023


Hello,

I have this class DataSource

data family DataSourcePath a :: Type
data family DataSourceAcq a :: Type

class DataSource a where
  withDataSourceP :: (Location l, MonadSafe m) => l -> DataSourcePath a -> (DataSourceAcq a -> m r) -> m r

The purpose is to acquire a ressources from a data source path (for example, in a hdf5 file, "hdf5://path/to/my/dataset" I need to obtain a C struct which point on the Dataset) and then do something with this ressources

Here an example of an instance in order to extract an Angstrom from a file or provide directly the constant value.

-- Angstrom

data instance DataSourcePath Angstrom = DataSourcePath'Angstrom (Hdf5Path Z Double)
                                       | DataSourcePath'Angstrom'Const Angstrom
  deriving (Eq, Generic, Show, FromJSON, ToJSON)

data instance DataSourceAcq Angstrom = DataSourceAcq'Angstrom Dataset
                                      | DataSourceAcq'Angstrom'Const Angstrom

instance DataSource Angstrom where
  withDataSourceP f (DataSourcePath'Angstrom p) g = withHdf5PathP f p $ \ds -> g (DataSourceAcq'Angstrom ds)
  withDataSourceP _ (DataSourcePath'Angstrom'Const a) g = g (DataSourceAcq'Angstrom'Const a)


next, I build a bunch of DataFrame which contain all these ressources.


data DataFrameQCustom
    = DataFrameQCustom
      Attenuation -- attenuation
      Geometry -- geometry
      Image -- image
      Index -- timestamp in double
    deriving Show

data instance DataSourcePath DataFrameQCustom
  = DataSourcePath'DataFrameQCustom
    (DataSourcePath Attenuation)
    (DataSourcePath Geometry)
    (DataSourcePath Image)
    (DataSourcePath Index)
  deriving (Eq, Generic, Show, FromJSON, ToJSON)

data instance DataSourceAcq DataFrameQCustom
  = DataSourceAcq'DataFrameQCustom
    (DataSourceAcq Attenuation)
    (DataSourceAcq Geometry)
    (DataSourceAcq Image)
    (DataSourceAcq Index)

Indded I now need to write the withDataSource instance by hand

instance DataSource DataFrameQCustom where
  withDataSourceP f (DataSourcePath'DataFrameQCustom a g i idx) gg =
    withDataSourceP f a $ \a' ->
    withDataSourceP f g $ \g' ->
    withDataSourceP f i $ \i' ->
    withDataSourceP f idx $ \idx' -> gg (DataSourceAcq'DataFrameQCustom a' g' i' idx')

this seems so mechanical that I am wondring if this should not be automatize via Generic.

Another point would be to avoiding mistake when writting the DatasourcePath instance and Generate the from an uniq structure using HKD

Something like

-- "Higher-Kinded Data"
type family HKD f a where
  HKD Identity a = a
  HKD f        a = f a

data DataFrameHkl' f
  = DataFrameHkl
    (HKD f DataFrameQCustom)
    (HKD f Sample)
  deriving (Generic)


type DataFrameHkl = DataFrameHkl' Identity
type DataFrameHklPath =  DataFrameHkl' DataSourcePath


so I would like your help in order to write first a Generic version of withDataSourceP

I read this https://reasonablypolymorphic.com/blog/higher-kinded-data/ but I am not completly sure how to convert my

  withDataSourceP :: (Location l, MonadSafe m) => l -> DataSourcePath a -> (DataSourceAcq a -> m r) -> m r

signature into something Generic

Thanks for considering

Fred


More information about the Haskell-Cafe mailing list