vary
Vary: Friendly and fast polymorphic variants (open unions/coproducts/extensible sums)
https://github.com/qqwy/haskell-vary#readme
LTS Haskell 24.16: | 0.1.1.3 |
Stackage Nightly 2025-10-24: | 0.1.1.3 |
Latest on Hackage: | 0.1.1.3 |
vary-0.1.1.3@sha256:9b93eb580b00a5a0b54bb729f72a13d497637b34c0c95b7661883207af84a01a,6944
Module documentation for 0.1.1.3
Vary: friendly and fast Variant types for Haskell
Just like tuples are a version of a user-defined product type (only without the field names), a Variant is a version of a user-defined sum type (but without the field names).
In other words: Variant types are the generalization of Either
to more (or less) than two alternatives.
Product: | Sum: |
---|---|
() | Vary [] / Void |
Solo a | Vary [a] |
(a, b) | Vary [a, b] / Either a b |
(a, b, c) | Vary [a, b, c] |
(a, b, c, d) | Vary [a, b, c, d] |
(…) | Vary […] |
Especially when doing error handling (both in pure code and in exception-heavy code), Variant types are a great abstraction to use.
Variant types are sometimes called ‘polymorphic variants’ for disambiguation. They are also commonly known as (open) unions, coproducts or extensible sums.
Vary is lightweight on dependencies. With all library flags turned off, it only depends on base
and deepseq
.
General Usage
Setup
The modules in this library are intended to be used qualified:
import Vary (Vary, (:|))
import qualified Vary
import Vary.VEither (VEither(VLeft, VRight))
import qualified Vary.VEither as VEither
The library is intended to be used with the following extensions active:
{-# LANGUAGE DataKinds #-}
-- As of GHC >= 9.2, you can replace the following three extensions by GHC2021 instead:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
Simple usage
You can construct Vary
using Vary.from
:
int_or_string :: Bool -> Vary '[Int, String]
int_or_string bool =
if bool then
Vary.from @Int 42
else
Vary.from @String "hello world"
-- You can also use the more general type,
-- which allows you to use a function to insert elements into any variant
-- that happens to contain the given type(s),
-- regardless of order or what other types are in its list:
int_or_string2 :: (Int :| l, String :| l) => Bool -> Vary l
int_or_string2 bool =
if bool then
Vary.from @Int 69
else
Vary.from @String "I like cheese"
You can check whether a particular variant is inside and attempt to extract it using Vary.into
:
maybe_an_int :: Bool -> Maybe Int
maybe_an_int bool = Vary.into @Int (int_or_string bool)
And you can match the various possibilities using Vary.on
, together with Vary.exhaustiveCase
if you’ve handled all cases:
stringify vary =
vary &
( Vary.on @String (\string -> "Found a string: " <> show string)
$ Vary.on @Int (\int -> "Found an int: " <> show int)
$ Vary.exhaustiveCase
)
It is generally recommended to keep the type generic at the place you construct a Vary
(using Vary.from
), and make the type concrete at the place you use it (for instance when using Vary.on
or Vary.into
).
This way, the construction functions can be used in any context, regardless of what other possibilities the caller might want to handle. (See also the ‘motivation’ example below).
In some cases you already have a concrete Vary
type, and you want to pass it to or return it from a function expecting another shape (different order of elements, having less or more elements). In those cases, Vary.morph
will help you out :-).
VEither
You have now seen Vary
. There is the closely related type VEither
. Its runtime representation is the same. The difference between Vary (a : errs)
and VEither errs a
is that while Vary
considers all types in its list of possibilities to be equal, VEither
considers the a
to be a ‘success’ (VRight
), whereas any of the types in errs
are considered ‘errors’ (VLeft
).
This means that VEither
can implement Functor
, Applicative
, Monad
, Foldable
, Traversable
, Generic
and a few other fun typeclasses, making it really easy to use for error handling.
Motivation: Why is ‘Vary’ useful?
Say we are writing an image thumbnailing service.
-
Given an image URL
-
We attempt to download it.
- This can fail, because the URL is incorrect;
- Or the URL /is/ correct but the server could not be reached (in which case we want to re-try later);
- Or the server /could/ be reached, but downloading took longer than a set time limit.
-
We pass it to a thumbnailing program.
- This can fail, because the downloaded file might turn out actually not to be a valid image file (PNG or JPG);
- Or even if the downloaded file /is/ an image, it might have a much too high resolution to attempt to read;
(NOTE: For simplicity, we pretend everything is a pure function rather than using IO or some more fancy effect stack in the examples below.)
The first instinct might be to write dedicated sum types for these errors like so:
data Image = Image
deriving (Eq, Show)
data DownloaderError1
= IncorrectUrl1
| ServerUnreachable1
| DownloadingTimedOut1
deriving (Eq, Ord, Show)
data ThumbnailError1
= NotAnImage1
| TooBigImage1
deriving (Eq, Ord, Show)
download1 :: String -> Either DownloaderError1 Image
download1 url =
-- Pretend we're doing hard work here
Right Image
thumbnail1 :: Image -> Either ThumbnailError1 Image
thumbnail1 image =
-- Pretend we're huffing and puffing
Right Image
But if we try to plainly combine these two functions, we get a compiler error:
thumbnailService1 url = do
image <- download1 url
thumb <- thumbnail1 image
pure thumb
error:
• Couldn't match type ‘ThumbnailError’ with ‘DownloaderError’
Expected: Either DownloaderError Image
Actual: Either ThumbnailError Image
We could 'solve' this problem by adding yet another manual error type:
data ThumbnailServiceError1
= DownloaderError1 DownloaderError1
| ThumbnailError1 ThumbnailError1
deriving (Eq, Ord, Show)
thumbnailService2 :: String -> Either ThumbnailServiceError1 Image
thumbnailService2 url = do
image <- first DownloaderError1 $ download1 url
thumb <- first ThumbnailError1 $ thumbnail1 image
pure thumb
This ‘works’, although already we can see that we’re doing a lot of manual ceremony to pass the errors around.
And wait! We wanted to re-try in the case of a ServerUnreachable
error!
waitAndRetry = undefined :: Word -> (() -> a) -> a
thumbnailServiceRetry2 :: String -> Either ThumbnailServiceError1 Image
thumbnailServiceRetry2 url =
case download1 url of
Left ServerUnreachable1 -> waitAndRetry 10 (\_ -> thumbnailServiceRetry2 url)
Left other -> Left (DownloaderError1 other)
Right image -> do
thumb <- first ThumbnailError1 $ thumbnail1 image
pure thumb
We now see:
- Even inside
thumbnailService
there now is quite a bit of ceremony w.r.t. wrapping,unwrapping and mapping between error types. - Callers will be asked to pattern match on the @ServerUnreachable@ error case,
even though that case will already be handled inside the
thumbnailService
function itself! - Imagine what happens when using this small function in a bigger system with many more errors! Do you keep defining more and more wrapper types for various combinations of errors?
There is a better way!
With the Vary
and related Vary.VEither.VEither
types, you can mix and match individual errors (or other types) at the places they are used.
import Vary (Vary, (:|))
import qualified Vary
import Vary.VEither (VEither(..))
import qualified Vary.VEither as VEither
data IncorrectUrl2 = IncorrectUrl2 deriving (Eq, Ord, Show)
data ServerUnreachable2 = ServerUnreachable2 deriving (Eq, Ord, Show)
data DownloadingTimedOut2 = DownloadingTimedOut2 deriving (Eq, Ord, Show)
data NotAnImage2 = NotAnImage2 deriving (Eq, Ord, Show)
data TooBigImage2 = TooBigImage2 deriving (Eq, Ord, Show)
download :: (ServerUnreachable2 :| err, IncorrectUrl2 :| err) => String -> VEither err Image
download url =
-- Pretend a lot of network communication happens here
VRight Image
thumbnail :: (NotAnImage2 :| err, TooBigImage2 :| err) => Image -> VEither err Image
thumbnail image =
-- Pretend this is super hard
VRight Image
Here is the version without the retry:
thumbnailService :: String -> VEither [ServerUnreachable2, IncorrectUrl2, NotAnImage2, TooBigImage2] Image
thumbnailService url = do
image <- download url
thumb <- thumbnail image
pure thumb
And here is all that needed to change to have a retry:
thumbnailServiceRetry :: String -> VEither [IncorrectUrl2, NotAnImage2, TooBigImage2] Image
thumbnailServiceRetry url = do
image <- VEither.handle @ServerUnreachable2 retry $ download url
thumb <- thumbnail image
pure thumb
where
retry _err = waitAndRetry 10 (\_ -> thumbnailServiceRetry url)
- No more wrapper type definitions!
- Handing an error makes it disappear from the output type!
Why anoher Variant library?
I am aware of the following Haskell libraries offering support for Variant types already:
Vary improves upon them in the following ways:
- Function names in these libraries are long and repetitive, and often seem to be very different from names used elsewhere in
base
or the community.Vary
is intended to be usedqualified
, making the function names short and snappy, and allowing re-use of names likemap
,from
,on
andinto
.
- Many libraries define their variant type using a Higher Kinded Data pattern. This is really flexible, but not easy on the eyes.
Vary
’s type is readable, which is what you want for the common case of using them for error handling.- It also means less manual type signatures are needed :-).
- Many libraries (exceptions:
fastsum
,haskus
) define their variant as a GADT-style linked-list-like datatype. The advantage is that you need nounsafeCoerce
anywhere. The disadvantage is that this has a huge runtime overhead.Vary
uses a single (unwrapped, strict) Word for the tag. GHC is able to optimize this representation very well!- Conversion between different variant shapes are also constant-time, as only this tag number needs to change.
- With the exception of
world-peace
andhaskus
, documentation of the libraries is very sparse.- All of the functions in
Vary
are documented and almost all of them have examples. (Doctested by the way!)
- All of the functions in
- The libraries try to make their variant be ‘everything it can possibly be’ and provide not only functions to work with variants by type, but also by index, popping, pushing, concatenating, handling all cases using a tuple of functions, etc. This makes it hard for a newcomer to understand what to use when.
Vary
intentionally only exposes functions to work by type.- There is one way to do case analysis of a
Vary
, namely usingVary.on
. Only one thing to remember! - Many shape-modification functions were combined inside
Vary.morph
, so you only ever need that one! - Only the most widely-useful functions are provided in
Vary
itself. There are some extra functions inVary.Utils
which are intentionally left out of the main module to make it more digestible for new users.
- Libraries are already many years old (with no newer updates), and so they are not using any of the newer GHC extensions or inference improvements.
Vary
makes great use of theGHC2021
group of extensions, TypeFamilies and theTypeError
construct to make most type errors disappear and for the few that remain it should be easy to understand how to fix them.
- None of the libraries make an attempt to work well with Haskell’s exception mechanisms.
Acknowledgements
This library stands on the shoulders of giants.
In big part it was inspired by the great Variant abstraction which exists in PureScript (and related VEither).
Where PureScript has a leg up over Haskell is in its support of row types. To make the types nice to use in Haskell even lacking row typing support was a puzzle in which the Effectful library gave great inspiration (and some type-level trickery was copied essentially verbatim from there.)
Finally, a huge shoutout to the pre-existing Variant libraries in Haskell. Especially to haskus-utils-variant and world-peace and the resources found in this blog post by world-peace’s author.
Is it any good?
Yes ;-)
Changes
Changelog for vary
All notable changes to this project will be documented in this file.
The format is based on Keep a Changelog, and this project adheres to the Haskell Package Versioning Policy.
Unreleased
0.1.1.3 - 2025-06-17
- Raise the max bound of QuickCheck. Before: >=2.12 && < 2.16. After: >=2.12 && < 3
0.1.1.2 - 2025-04-16
- Lower the minimum supported GHC version to v8.10.x by removing internal usage of
GHC2021
. (PR #9) Thank you, @newhoggy and @carbolymer!
0.1.1.1 - 2025-02-06
- Loosen test dependency bound on QuickCheck.
0.1.1.0 - 2025-02-05
- Add serialization support of
Vary
forbinary
’sData.Binary
andcereal
’sData.Serialize
. (c.f. #6) Thank you very much, @jmorag! - Document
Data.Aeson
round-tripping behaviour (namely: only round-trippable if encodings do not overlap, theUntaggedValue
sum encoding).
0.1.0.5 - 2025-02-05
- Relax max allowed versions of DeepSeq (<1.6), Hashable (<1.6), QuickCheck (<2.16)
0.1.0.4 - 2024-01-15
- Improved test coverage for exception cases; README is now fully tested using Literate Haskell.
0.1.0.3 - 2024-01-14
- Fix a typographic error in the documentation
0.1.0.2 - 2024-01-14
- Improve documentation
0.1.0.0 - 2024-01-13
- Initial version