The encoding based on “single-step/shallow” case analysis is called Scott encoding. The encoding based on “deep” folds is called Church encoding.
Thanks for clarifying. I keep confusing the two.
Thanks for this, I hadn’t heard of Scott encoding before.
I found this article which I was able to re-implement (except for some flipping of arguments) using my library, both with ChainsL
and NP (ChainF r)
(which are totally equivalent, but it was fun to work it out with both).
Most of the code is shared - you can toggle between the 2 by commenting out the line #define USE_NP
.
The only difference is that the machinery from generics-case
won’t do the “deep” folds as described above, since that’s generics-sop
works. This is why we sometimes have to convert between the representations (see numToPeano
, listToListS
and listSToList
). I suppose it might be possible to do a proper encoding as in the article, using the ChainFoldF
from the gist I posted earlier.
Edit: One think that was missing (now corrected, and I’ll probably add it to the library) from the above gist:
something :: forall a. (Generic a, All SListI (Code a)) => NP (ChainF a) (Code a)
It took a bit of squinting for me to realise what this was (equivalent to): a heterogenous list of all the constructors of a dataype. Can we do this? Well:
constructors' :: forall xss. (All SListI xss) => NP (ChainF (NS (NP I) xss)) xss
constructors' = case sList @xss of
SNil -> Nil
SCons -> ChainF Z :* hliftA (ChainF . (S .) . applyChain) constructors'
constructors :: forall a. (Generic a, All SListI (Code a)) => NP (ChainF a) (Code a)
constructors = hliftA (ChainF . ((to . SOP) .) . applyChain) $ constructors' @(Code a)
We can test the implementation by constructing the most elaborate identity function I’ve ever written:
idTheLongWayRound :: forall a. (Generic a, All SListI (Code a)) => a -> a
idTheLongWayRound = applyNSChain constructors . from
ghci> idTheLongWayRound (Just 2 :: Maybe Int)
Just 2
ghci> idTheLongWayRound (Left "abc" :: Either String ())
Left "abc"
Update
After playing around with the concepts a lot, I realised I could simplify a lot of the code here. The ChainF
newtype was just adding overhead (both cognitive and performance); recursively constructing and destructing NP
s of the analysis functions was very inefficient. The code is now half the size, more readable, and more than an order of magnitude faster - performance is now much closer to a hand-written function like maybe
. Here’s the PR.
The only drawback is a reduction in flexibility: before this change we had gcaseL
(datatype before analysis functions) and gcaseR
(analysis functions before datatype). Now we only have gcase
, which is semantically identical to gcaseL
. In other words, we’ve lost the ability to put the datatype after the functions, as in maybe
, either
, and bool
. Price of progress.
I’ve uploaded the updated code + docs to Hackage, it should be displayed soon (if you see is available now.gcaseR
, it hasn’t updated its cache yet)
Again, all feedback welcome
Update: version 0.1.0.0
of generic-case
is now published. Feedback and PRs still very welcome
I haven’t looked at this deeply, but I think this is a pretty big drawback! Putting the analysis functions first is usually more ergonomic. let toErr = maybe (Left err) Right in ...
(edit) Not to rain on your parade though - congrats on the release, the library looks cool.
Thanks for the feedback Bryan! You’re absolutely right, it is much more ergonomic, and I get why that might be a dealbreaker for some. So, just for you, I had another crack at implementing gcaseR
:
I’ve provisionally uploaded the new docs as a candidate for version 0.1.1.0
:
https://hackage.haskell.org/package/generic-case-0.1.1.0/candidate
Any thoughts on the PR would be appreciated
Version 0.1.1.0, with gcaseR
, is now published on Hackage. gcaseR
does the same thing as the original gcase
, except it now follows the same shape as maybe
and either
: the datatype in question is the final argument, after the analysis functions.
There’s a warning in the docs about performance, but I’ll copy it here:
This is undoubtedly more ergonomic, since it allows us to use partial application nicely:
let maybeToEither err = maybeR (Left err) Right
in ...
However, this carries a slight performance impact. It will always be faster to use gcase
, so if performance is critical in your use-case, use that. Then again, if performance is really critical, you’ll always be better off writing your analysis function manually; or just pattern-matching directly.