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 <monkleyon@gmail.com> wrote:
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.