How to write a Monad instance for this type

Hello, I try to write a monad instance for this type which represent the content of an hdf5 file. This file format is similar to a filesystem, where directories are Group and files Dataset. I end up with this type. data Hdf5M a = H5Root (Hdf5M a) | H5Group ByteString [Hdf5M a] -- A group can contain other groups and/or datasets | forall sh b. (NativeType b, Shape sh) => H5Dataset ByteString (Array F sh b) type Hdf5 = Hdf5M () hdf5 :: Hdf5 -> Hdf5 hdf5 = H5Root group :: ByteString -> [Hdf5] -> Hdf5 group g = H5Group g dataset :: (NativeType b, Shape sh) => ByteString -> (Array F sh b) -> Hdf5 dataset = H5Dataset I tryed to inspire myself from the blaze-html Markup type. And I would like to be able to describe a contain like this hdf5 $ do group "name" $ do dataset "name1" array1 dataset "name2" array2 group "other-name" $ do etc... instead of H5Root ( H5Group "name" [ dataset ]...) the final idea, is to be able to serialize object via a class ToHdf5 where toHdf5 :: a -> Hdf5 So my question is someone can help me design this ? thanks for your help Frederic

Hello Frederic, you might want to take a look at /free monads/ http://www.haskellforall.com/2012/06/you-could-have-invented-free-monads.htm... and the free library http://hackage.haskell.org/package/free-5.1.1. Cheers, Tobias On 9/2/19 9:20 PM, PICCA Frederic-Emmanuel wrote:
Hello, I try to write a monad instance for this type which represent the content of an hdf5 file. This file format is similar to a filesystem, where directories are Group and files Dataset.
I end up with this type.
data Hdf5M a = H5Root (Hdf5M a) | H5Group ByteString [Hdf5M a] -- A group can contain other groups and/or datasets | forall sh b. (NativeType b, Shape sh) => H5Dataset ByteString (Array F sh b)
type Hdf5 = Hdf5M ()
hdf5 :: Hdf5 -> Hdf5 hdf5 = H5Root
group :: ByteString -> [Hdf5] -> Hdf5 group g = H5Group g
dataset :: (NativeType b, Shape sh) => ByteString -> (Array F sh b) -> Hdf5 dataset = H5Dataset
I tryed to inspire myself from the blaze-html Markup type.
And I would like to be able to describe a contain like this
hdf5 $ do group "name" $ do dataset "name1" array1 dataset "name2" array2 group "other-name" $ do etc...
instead of
H5Root ( H5Group "name" [ dataset ]...)
the final idea, is to be able to serialize object via a
class ToHdf5 where toHdf5 :: a -> Hdf5
So my question is someone can help me design this ?
thanks for your help
Frederic _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Hi.
I end up with this type.
data Hdf5M a = H5Root (Hdf5M a) | H5Group ByteString [Hdf5M a] -- A group can contain other groups and/or datasets | forall sh b. (NativeType b, Shape sh) => H5Dataset ByteString (Array F sh b)
[…]
And I would like to be able to describe a contain like this
hdf5 $ do group "name" $ do dataset "name1" array1 dataset "name2" array2 group "other-name" $ do etc...
You don't need a monad instance for this. First of all, you don't even need do syntax to make something "pretty" similar to this. hdf5 $ group "name" $ [ dataset "name1" array1 , dataset "name2" array2 , group "other-name" $ [ … But if you insist, you can just use an existing monad like WriterT. For example (simplified): data Composite a = Base a | Composite [Composite a] type CompositeWriter a = Writer [Composite a] () base = tell . pure . Base composite = censor (pure . Composite) asComposite = Composite . snd . runWriter test = asComposite $ do base 'a' base 'b' composite $ do base 'c' base 'd' Hope that helps.

Being able to omit []'s and commas is a very natural desire, and it's not
clear why would anyone need to engage with monads to achieve this. Although
today monads is probably the only way (NB: look at the RebindableSyntax
extension), there were a number of discussions over GHC Proposals as to how
to retrofit it into the language, e.g. [Record with Syntax][Record-with].
This and (closed unmerged) the [Extra Commas][Extra-Commas] proposal
prompted Joachim to start a [wiki page][All-things-layout] gathering this
kind of ideas — which I highly recommend to check out and, possibly,
brainstorm. Hopefully, it will turn into a new, this time successful GHC
proposal.
[Extra-Commas]: https://github.com/ghc-proposals/ghc-proposals/pull/87
[Record-with]: https://github.com/ghc-proposals/ghc-proposals/pull/231
[All-things-layout]:
https://gitlab.haskell.org/ghc/ghc/wikis/All-things-layout
--
Kind regards, Artem
On Tue, 3 Sep 2019 at 13:42, MarLinn
Hi.
I end up with this type.
data Hdf5M a = H5Root (Hdf5M a) | H5Group ByteString [Hdf5M a] -- A group can contain other groups and/or datasets | forall sh b. (NativeType b, Shape sh) => H5Dataset ByteString (Array F sh b)
[…]
And I would like to be able to describe a contain like this
hdf5 $ do group "name" $ do dataset "name1" array1 dataset "name2" array2 group "other-name" $ do etc...
You don't need a monad instance for this. First of all, you don't even need do syntax to make something "pretty" similar to this.
hdf5 $ group "name" $ [ dataset "name1" array1 , dataset "name2" array2 , group "other-name" $ [ …
But if you insist, you can just use an existing monad like WriterT. For example (simplified):
data Composite a = Base a | Composite [Composite a]
type CompositeWriter a = Writer [Composite a] ()
base = tell . pure . Base
composite = censor (pure . Composite)
asComposite = Composite . snd . runWriter
test = asComposite $ do base 'a' base 'b' composite $ do base 'c' base 'd'
Hope that helps. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

You don't need a monad instance for this. First of all, you don't even need do syntax to make something "pretty" similar to this.
hdf5 $ group "name" $ [ dataset "name1" array1 , dataset "name2" array2 , group "other-name" $ [ …
This is for now the solution I decide to keep., nevertheless thanks for the monad ;). Now I would like you opinion about a type which allows me to select a node in this tree. I need to extract a bunch of values from these hdf5 files. So I discribe a location in the tree, like this with another type quite similar to the first but with only one child per group. This way there is only one dataset extracted. (maybe later, I will discuss about extracting multiple dataset ;). data Hdf5Path sh e = H5RootPath (Hdf5Path sh e) | H5GroupPath ByteString (Hdf5Path sh e) | H5DatasetPath ByteString hdf5p $ group "name" $ group "otherName" $ dataset "myDataset" Then I need to write something like this. withDataset :: File -> Hdf5Path sh e -> (Dataset -> IO r) -> IO r BUT, I would like to express this path like this hdf5p :: group <the first encounted> :: group "otherName" $ dataset "mydataset" So should I define a type and modify the group constructor like this H5GroupPath BytString (Hdf5Path sh e) GroupDesc = ByName ByteString | ByPosition Int | etc... H5GroupPath GropDesc (Hdf5Path sh e) the only problem I see with this is that I need to encode all the strategies in this type. Is there a better way to do this sort of things. thanks Frederic

Hi Frederic,
Lenses (http://hackage.haskell.org/package/lens) are a powerful and well-supported way of peering into data structures. They are a bit of work to learn, but well worth it.
Will
On Sep 6, 2019, at 4:58 PM, PICCA Frederic-Emmanuel
You don't need a monad instance for this. First of all, you don't even need do syntax to make something "pretty" similar to this.
hdf5 $ group "name" $ [ dataset "name1" array1 , dataset "name2" array2 , group "other-name" $ [ …
This is for now the solution I decide to keep., nevertheless thanks for the monad ;).
Now I would like you opinion about a type which allows me to select a node in this tree.
I need to extract a bunch of values from these hdf5 files. So I discribe a location in the tree, like this with another type quite similar to the first but with only one child per group. This way there is only one dataset extracted.
(maybe later, I will discuss about extracting multiple dataset ;).
data Hdf5Path sh e = H5RootPath (Hdf5Path sh e) | H5GroupPath ByteString (Hdf5Path sh e) | H5DatasetPath ByteString
hdf5p $ group "name" $ group "otherName" $ dataset "myDataset"
Then I need to write something like this.
withDataset :: File -> Hdf5Path sh e -> (Dataset -> IO r) -> IO r
BUT, I would like to express this path like this
hdf5p :: group <the first encounted> :: group "otherName" $ dataset "mydataset"
So should I define a type and modify the group constructor like this
H5GroupPath BytString (Hdf5Path sh e)
GroupDesc = ByName ByteString | ByPosition Int | etc...
H5GroupPath GropDesc (Hdf5Path sh e)
the only problem I see with this is that I need to encode all the strategies in this type.
Is there a better way to do this sort of things.
thanks
Frederic _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

So I discribe a location in the tree, like this with another type quite similar to the first but with only one child per group. This way there is only one dataset extracted.
(maybe later, I will discuss about extracting multiple dataset ;).
data Hdf5Path sh e = H5RootPath (Hdf5Path sh e) | H5GroupPath ByteString (Hdf5Path sh e) | H5DatasetPath ByteString
hdf5p $ group "name" $ group "otherName" $ dataset "myDataset"
Is there a better way to do this sort of things.
The answer to this depends a lot on how powerful you want your path to be. But the easiest way would probably be to just wrap functions: -- can be used with functions from Data.List data Path a = GroupPath ([Hdf5M a] -> Hdf5M a) (Path a) | … test = hdf5p $ group head $ group (firstOfName "otherName") $ dataset "mydataset" test2 = hdf5p $ group (!! 6) $ group (firstOfName "otherName") $ dataset "mydataset" firstOfName n = fromJust . (find $ hasName n) hasName :: ByteString -> Hdf5M a -> Bool Or if you want more restrictions on which types of paths can be constructed data Path a = GroupPathWithFilter (Hdf5M a -> Bool) (Path a) | GroupPathByIndex Int (Path a) … -- equivalent to "head" test = hdf5p $ group (const True) $ group (hasName "otherName") $ dataset "mydataset" test2 = hdf5p $ groupAt 6 $ group (hasName "otherName") $ dataset "mydataset" Side note: I don't see a reason why the path needs to be recursive if this is all you want. type Path a = [PathSegment a] data PathSegment a = GroupPath (Hdf5M a -> Bool) | … test = hdf5p [group (const True) , group (hasName "otherName") , dataset "mydataset"] What if you want something more like an XPath or a path with wildcards? You can still expand on these ideas easily. type Path a = [PathSegment a] data PathSegment a = GroupPath ([Hdf5M a] -> [Hdf5M a]) | … test = hdf5p [group (pure . head) , group (filter $ hasName "otherName") , dataset "mydataset"] test2 = hdf5p [group (pure . (!! 6)) , group (filter $ hasName "otherName") , dataset "mydataset"] -- or more likely test = hdf5p [group head , groups (hasName "otherName") , dataset "mydataset"] test2 = hdf5p' [group (!! 6) , groups (hasName "otherName") , dataset "mydataset"] -- But these are basically just lists of [Hdf5M a] → [Hdf5M a] functions with one special function -- at the end – which can also be cast as such a function. Therefore something like this would also be possible: newtype Path a = Path [[Hdf5M a] -> [Hdf5M a]] compilePath (Path fs) = filter isDataset . foldl1 (.) fs -- Path can also be turned into a monoid now test = hdf5p $ group head <> groups (hasName "otherName") <> dataset "mydataset" -- which also means it would be prudent to reduce this to newtype Path a = Path ([Hdf5M a] -> [Hdf5M a]) While this final solution looks quite elegant from my POV, there are several directions this can't be extended into as easily as the recursive tree. So this is just a bunch of options from a few minutes of brainstorming, the best option for your particular problem is probably somewhere between these and the ones you already had. Cheers.

thanks I lot for your time, I will think about this for my use cases :) Cheers Frederic ________________________________________ De : MarLinn [monkleyon@gmail.com] Envoyé : vendredi 6 septembre 2019 14:51 À : PICCA Frederic-Emmanuel; haskell-cafe@haskell.org Objet : Re: [Haskell-cafe] How to write a Monad instance for this type So I discribe a location in the tree, like this with another type quite similar to the first but with only one child per group. This way there is only one dataset extracted. (maybe later, I will discuss about extracting multiple dataset ;). data Hdf5Path sh e = H5RootPath (Hdf5Path sh e) | H5GroupPath ByteString (Hdf5Path sh e) | H5DatasetPath ByteString hdf5p $ group "name" $ group "otherName" $ dataset "myDataset" Is there a better way to do this sort of things. The answer to this depends a lot on how powerful you want your path to be. But the easiest way would probably be to just wrap functions: -- can be used with functions from Data.List data Path a = GroupPath ([Hdf5M a] -> Hdf5M a) (Path a) | … test = hdf5p $ group head $ group (firstOfName "otherName") $ dataset "mydataset" test2 = hdf5p $ group (!! 6) $ group (firstOfName "otherName") $ dataset "mydataset" firstOfName n = fromJust . (find $ hasName n) hasName :: ByteString -> Hdf5M a -> Bool Or if you want more restrictions on which types of paths can be constructed data Path a = GroupPathWithFilter (Hdf5M a -> Bool) (Path a) | GroupPathByIndex Int (Path a) … -- equivalent to "head" test = hdf5p $ group (const True) $ group (hasName "otherName") $ dataset "mydataset" test2 = hdf5p $ groupAt 6 $ group (hasName "otherName") $ dataset "mydataset" Side note: I don't see a reason why the path needs to be recursive if this is all you want. type Path a = [PathSegment a] data PathSegment a = GroupPath (Hdf5M a -> Bool) | … test = hdf5p [group (const True) , group (hasName "otherName") , dataset "mydataset"] What if you want something more like an XPath or a path with wildcards? You can still expand on these ideas easily. type Path a = [PathSegment a] data PathSegment a = GroupPath ([Hdf5M a] -> [Hdf5M a]) | … test = hdf5p [group (pure . head) , group (filter $ hasName "otherName") , dataset "mydataset"] test2 = hdf5p [group (pure . (!! 6)) , group (filter $ hasName "otherName") , dataset "mydataset"] -- or more likely test = hdf5p [group head , groups (hasName "otherName") , dataset "mydataset"] test2 = hdf5p' [group (!! 6) , groups (hasName "otherName") , dataset "mydataset"] -- But these are basically just lists of [Hdf5M a] → [Hdf5M a] functions with one special function -- at the end – which can also be cast as such a function. Therefore something like this would also be possible: newtype Path a = Path [[Hdf5M a] -> [Hdf5M a]] compilePath (Path fs) = filter isDataset . foldl1 (.) fs -- Path can also be turned into a monoid now test = hdf5p $ group head <> groups (hasName "otherName") <> dataset "mydataset" -- which also means it would be prudent to reduce this to newtype Path a = Path ([Hdf5M a] -> [Hdf5M a]) While this final solution looks quite elegant from my POV, there are several directions this can't be extended into as easily as the recursive tree. So this is just a bunch of options from a few minutes of brainstorming, the best option for your particular problem is probably somewhere between these and the ones you already had. Cheers.
participants (5)
-
Artem Pelenitsyn
-
MarLinn
-
PICCA Frederic-Emmanuel
-
Tobias Brandt
-
Will Yager