vary-0.1.0.3: Vary: Friendly and fast polymorphic variants (open unions/coproducts/extensible sums)
Safe HaskellSafe-Inferred
LanguageHaskell2010

Vary

Synopsis

General Usage

Setup

This module is intended to be used qualified:

>>> import Vary (Vary, (:|))
>>> import qualified Vary

You probably often want to use it together with the Vary.VEither module:

>>> import Vary.VEither (VEither(VLeft, VRight))
>>> import qualified Vary.VEither as VEither

And for many functions, it is useful (and sometimes outright necessary) to enable the following extensions:

>>> -- Of the GHC2021 set, Vary uses: TypeApplications, TypeOperators, FlexibleContexts:
>>> :set -XGHC2021
>>> :set -XDataKinds

Finally, some example snippets in this module make use of &, the left-to-right function application operator.

>>> import Data.Function ((&))

Motivating Example

A longer example on why you would want to use Vary can be found in the package README on GitHub

Vary and Exceptions

Vary implements Exception, and is an excellent type to use with throw and catch.

>>> import Control.Exception
>>> no_xyzzy  = Vary.from (NoMethodError "xyzzy") :: Vary '[NoMethodError, ArithException]
>>> divby0    = Vary.from DivideByZero            :: Vary '[NoMethodError, ArithException]
>>> throw no_xyzzy `catch` \(e :: Vary '[NoMethodError, ArithException]) -> putStrLn ("Caught: `" <> show e <> "`")
Caught: `Vary.from @NoMethodError xyzzy`

Catching individual errors of a thrown Vary

toException is implemented to throw the particular internal type.

This means that you can catch any of the particular individual possibilities of a thrown Vary if you like, and have the others bubble up:

>>> throw no_xyzzy `catch` \(e :: NoMethodError) -> putStrLn ("Caught: `" <> show e <> "`")
Caught: `xyzzy`
>>> throw divby0 `catch` \(e :: NoMethodError) -> putStrLn ("Caught: `" <> show e <> "`")
*** Exception: divide by zero

Catching groups of (individually thrown) errors

Also, fromException is implemented to match any of the contained possibilities:

>>> catcher inner = inner `catch` \(e :: Vary '[NoMethodError, ArithException]) -> putStrLn ("Caught: `" <> show e <> "`")

So not only is the following exception caught:

>>> vary = Vary.from (NoMethodError "plover") :: Vary '[NoMethodError, ArithException]
>>> catcher (throw vary)
Caught: `Vary.from @NoMethodError plover`

But it will also catch a thrown ArithException

>>> catcher (throw DivideByZero)
Caught: `Vary.from @ArithException divide by zero`

or a thrown NoMethodError!

>>> catcher (throw (NoMethodError "plugh"))
Caught: `Vary.from @NoMethodError plugh`

(and other exceptions of course still bubble up)

>>> catcher (throw AllocationLimitExceeded)
*** Exception: allocation limit exceeded

Core type definition

data Vary (possibilities :: [Type]) Source #

Vary, contains one value out of a set of possibilities

Vary is what is known as a Variant type. This is also known as an open union or coproduct, among other names.

You can see it as the generalization of Either. Conceptually, these are the same:

Vary [a, b, c, d, e]
Either a (Either b (Either c (Either d e)))

However, compared to a deeply nested Either, Vary is:

  • Much easier to work with;
  • Much more efficient, as a single (strict) word is used for the tag.

Vary's can be constructed with Vary.from and values can be extracted using Vary.into and Vary.on .

Instances

Instances details
(Exception e, Exception (Vary errs), Typeable errs) => Exception (Vary (e ': errs)) Source #

See Vary and Exceptions for more info.

Instance details

Defined in Vary.Core

Methods

toException :: Vary (e ': errs) -> SomeException #

fromException :: SomeException -> Maybe (Vary (e ': errs)) #

displayException :: Vary (e ': errs) -> String #

(Typeable (Vary ('[] :: [Type])), Show (Vary ('[] :: [Type]))) => Exception (Vary ('[] :: [Type])) Source # 
Instance details

Defined in Vary.Core

(Typeable a, Show a, Show (Vary as)) => Show (Vary (a ': as)) Source #

Vary's Show instance only works for types which are Typeable

This allows us to print the name of the type which the current value is of.

>>> Vary.from @Bool True :: Vary '[Int, Bool, String]
Vary.from @Bool True
>>> Vary.from @(Maybe Int) (Just 1234) :: Vary '[Maybe Int, Bool]
Vary.from @(Maybe Int) (Just 1234)
Instance details

Defined in Vary.Core

Methods

showsPrec :: Int -> Vary (a ': as) -> ShowS #

show :: Vary (a ': as) -> String #

showList :: [Vary (a ': as)] -> ShowS #

Show (Vary ('[] :: [Type])) Source # 
Instance details

Defined in Vary.Core

Methods

showsPrec :: Int -> Vary '[] -> ShowS #

show :: Vary '[] -> String #

showList :: [Vary '[]] -> ShowS #

(NFData a, NFData (Vary as)) => NFData (Vary (a ': as)) Source # 
Instance details

Defined in Vary.Core

Methods

rnf :: Vary (a ': as) -> () #

NFData (Vary ('[] :: [Type])) Source # 
Instance details

Defined in Vary.Core

Methods

rnf :: Vary '[] -> () #

(Eq a, Eq (Vary as)) => Eq (Vary (a ': as)) Source # 
Instance details

Defined in Vary.Core

Methods

(==) :: Vary (a ': as) -> Vary (a ': as) -> Bool #

(/=) :: Vary (a ': as) -> Vary (a ': as) -> Bool #

Eq (Vary ('[] :: [Type])) Source # 
Instance details

Defined in Vary.Core

Methods

(==) :: Vary '[] -> Vary '[] -> Bool #

(/=) :: Vary '[] -> Vary '[] -> Bool #

(Ord a, Ord (Vary as)) => Ord (Vary (a ': as)) Source # 
Instance details

Defined in Vary.Core

Methods

compare :: Vary (a ': as) -> Vary (a ': as) -> Ordering #

(<) :: Vary (a ': as) -> Vary (a ': as) -> Bool #

(<=) :: Vary (a ': as) -> Vary (a ': as) -> Bool #

(>) :: Vary (a ': as) -> Vary (a ': as) -> Bool #

(>=) :: Vary (a ': as) -> Vary (a ': as) -> Bool #

max :: Vary (a ': as) -> Vary (a ': as) -> Vary (a ': as) #

min :: Vary (a ': as) -> Vary (a ': as) -> Vary (a ': as) #

Ord (Vary ('[] :: [Type])) Source # 
Instance details

Defined in Vary.Core

Methods

compare :: Vary '[] -> Vary '[] -> Ordering #

(<) :: Vary '[] -> Vary '[] -> Bool #

(<=) :: Vary '[] -> Vary '[] -> Bool #

(>) :: Vary '[] -> Vary '[] -> Bool #

(>=) :: Vary '[] -> Vary '[] -> Bool #

max :: Vary '[] -> Vary '[] -> Vary '[] #

min :: Vary '[] -> Vary '[] -> Vary '[] #

type (:|) e es = Member e es Source #

Constrain es to be any type list containing e.

Useful to talk about variants generically without having to specify the exact type list right away.

For instance, the type of from is

Vary.from :: (a :| l) => a -> Vary l

because we can use it to construct any Vary as long as there is an a somewhere in its list of types.

Construction and Destruction:

from :: forall a l. a :| l => a -> Vary l Source #

Builds a Vary from the given value.

>>> let thingy :: Vary [Bool, Char]; thingy = Vary.from 'a'
>>> thingy
Vary.from @Char 'a'

In the case of number literals or (with OverloadedStrings or OverloadedLists enabled) string or list literals, it might be necessary to include a TypeApplication. In most other cases, GHC is able to infer which possibility to use (though you might still like type applications even here for improved readability).

>>> Vary.from @Int 42 :: Vary [Int, String]
Vary.from @Int 42

In the case of the Vary contains duplicate types, the first matching type index is used.

into :: forall a l. a :| l => Vary l -> Maybe a Source #

Attempts to turn the Vary back into a particular type.

This might fail since the Vary might actually contain another possibility, which is why a Maybe is returned.

If you have a single possibility, you can use intoOnly instead.

Polymorphic functions

If you pass the result to a polymorphic function, GHC might not be able to infer which result type you'd like to try to extract. Indicate the desired result type using a TypeApplication:

>>> let vary = Vary.from @Bool True :: Vary [Bool, String]
>>> Vary.into @Bool vary
Just True

Type errors

Sometimes you might see nasty long type errors, containing the string Type_List_Too_Vague___Please_Specify_Prefix_Of_List_Including_The_Desired_Type's_Location.

This happens when other parts of your code keep the type list fully abstract (only use the :| constraint).

You can fix it by either giving a type to an intermediate value, or by passing a second type application to this function:

>>> let vary = if True then Vary.from True else Vary.from 'a' -- Inferred type: `Bool :| l, Char :| l => Vary l`
>>> Vary.into @Bool @(Char : Bool : _) vary
Just True

As you can see from the above example, it is often not necessary to specify the full type list. A prefix is commonly enough.

intoOnly :: forall a. Vary '[a] -> a Source #

Extract the value of a variant with one possibility.

A variant with only a single possibility can always be safely turned back into this one type.

If you have multiple possibilities, use into.

case analysis ("pattern matching"):

Vary does not support traditional pattern matching, because GHC is not able to check them for exhaustiveness.

Instead, Vary supports the next best thing: building up a pattern match using the on combinator.

on :: forall a b l. (a -> b) -> (Vary l -> b) -> Vary (a : l) -> b Source #

Handle a particular variant possibility.

This is the main way to do case analysis (or deconstruct) a variant.

Use it together with exhaustiveCase if you handle all possibilities, or defaultCase if you don't want to.

Even though in many cases GHC is able to infer the types, it is a good idea to combine it with TypeApplications:

Note that by doing so, GHC can infer the type of the function without problems:

>>> :{
  example vary =
    vary &
    ( Vary.on @Bool show
    $ Vary.on @Int (\x -> show (x + 1))
    $ Vary.defaultCase "other value"
    )
:}
>>> :t example
example :: Vary (Bool : Int : l) -> String

exhaustiveCase :: forall anything. Vary '[] -> anything Source #

Base case of an exhaustive pattern match.

Use it together with on, or whenever you have an empty `Vary '[]` that you need to get rid of. (Like in a recursive typeclass definition. See Vary.pop)

Since it is impossible to actually construct a value of the type Vary '[], we can "turn it into anything", just like absurd.

defaultCase :: forall a l. a -> Vary l -> a Source #

Base case of a non-exhaustive pattern match. Use it together with on.

If you've handled the variants you like and have some left, you can specify a default fallback value using defaultCase.

Indeed, this function is just another name for const.

pop :: Vary (a : as) -> Either (Vary as) a Source #

Attempts to extract a value of the first type from the Vary.

If this failed, we know it has to be one of the other possibilities.

This function can also be seen as turning one layer of Vary into its isomorphic Either representation.

This function is not often useful in normal code, but super useful in generic code where you want to recurse on the variant's types.

For instance when implementing a typeclass for any Vary whose elements implement the typeclass:

instance Show (Vary '[]) where
   show = Vary.exhaustiveCase

instance (Show a, Show (Vary as)) => Show (Vary (a : as)) where
   show vary = case Vary.pop vary of
       Right val -> "Vary.from " <> show val
       Left other -> show other

To go the other way:

  • Use Vary.morph to turn Vary as back into Vary (a : as)
  • Use Vary.from to turn a back into Vary (a : as)

Transforming

mapOn :: forall a b xs ys. Mappable a b xs ys => (a -> b) -> Vary xs -> Vary ys Source #

Run a function on one of the variant's possibilities, keeping all other possibilities the same.

This is the generalization of functions like Either's mapLeft and mapRight.

If you want to map a polymorphic function like show which could match more than one possibility, use a TypeApplication to specify the desired possibility to match:

>>> :{
(Vary.from @Int 42           :: Vary [Int, Bool] )
  & Vary.mapOn @Bool show    -- Vary [Int, String]
  & Vary.mapOn @Int show     -- Vary [String, String]
:}
Vary.from @[Char] "42"

If you end up with a variant with multiple duplicate possibilities, use morph to join them:

>>> :{
(Vary.from True                :: Vary [Char, Int, Bool])
  & Vary.mapOn @Bool show      -- Vary [Char, Int, String]
  & Vary.mapOn @Int show       -- Vary [Char, String, String]
  & Vary.mapOn @Char show      -- Vary [String, String, String]
  & Vary.morph @'[String]       -- Vary '[String]
  & Vary.intoOnly              -- String
:}
"True"

Note that if you end up handling all cases of a variant, you might prefer using on and exhaustiveCase instead.

Generic code

It is possible to use the most general type of this function in your own signatures; To do this, add the Mappable constraint (exposed from Utils) to relate the input variant with the output variant.

>>> import qualified Data.Char
>>> :{
example4 :: (Vary.Utils.Mappable Int Bool xs ys, Vary.Utils.Mappable Char Int ys zs) => Vary xs -> Vary zs
example4 vary =
  vary
  & Vary.mapOn @Int (\x -> x > 0)
  & Vary.mapOn @Char Data.Char.ord
:}

Duplicate possibilities

Vary.mapOn will only work on the first instance of the type that is encountered. This is only a problem if a possibility is in the list multiple times; be sure to morph duplicate possibilities away if needed.

morph :: forall ys xs. Subset xs ys => Vary xs -> Vary ys Source #

Extend a smaller Vary into a bigger one, change the order of its elements, or get rid of duplicates.

Extend a smaller Vary:

>>> small = Vary.from True :: Vary '[Bool]
>>> big = Vary.morph small :: Vary [Bool, Int, String]
>>> big
Vary.from @Bool True

Reorder elements:

>>> boolfirst = Vary.from @Int 42   :: Vary [Bool, Int]
>>> intfirst = Vary.morph boolfirst :: Vary [Int, Bool]
>>> intfirst
Vary.from @Int 42

Get rid of duplicate elements:

>>> duplicates = Vary.from @Int 69       :: Vary [Int, Int, Int]
>>> noduplicates = Vary.morph duplicates :: Vary '[Int]
>>> noduplicates
Vary.from @Int 69

Type applications

Morph intentionally takes the result type list as first type-application parameter. This allows you to write above examples in this more concise style instead:

>>> big = Vary.morph @[Bool, Int, String] small
>>> intfirst = Vary.morph @[Int, Bool] boolfirst
>>> noduplicates = Vary.morph @'[Int] duplicates

Efficiency

This is a O(1) operation, as the tag number stored in the variant is changed to the new tag number.

In many cases GHC can even look through the old->new Variant structure entirely, and e.g. inline the variant construction all-together.

morphed :: forall a b res. Subset a b => (Vary b -> res) -> Vary a -> res Source #

Execute a function expecting a larger (or differently-ordered) variant with a smaller (or differently-ordered) variant, by calling morph on it before running the function.