[Haskell-cafe] How to write a Monad instance for this type

MarLinn monkleyon at gmail.com
Fri Sep 6 12:51:09 UTC 2019


> 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.

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20190906/1aa307b5/attachment.html>


More information about the Haskell-Cafe mailing list