subzero-0.1.0.8: Helps when going "seed values" -> alternatives and optional -> answers

Copyright(c) Tristan Wibberley 2017
LicenseGPL-2
Maintainertristan.wibberley@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Applicative.SubZero

Contents

Description

Converts a functor so that each point at the source has alternatives to model things like a container of optional values, or of a variety of opinions about a point.

It turns out that Compose is ideal for this because Functor f => f a is isomorphic to Functor f => Compose f Identity a.

The gorgeous result is that two ZipLists of alternatives can zip together, providing an expanding set of alternatives to each point.

Here's how you can interpret Compose f g a:

f
The major functor, overall mapping/view
g
This has a few key useful interpretations depending on its instances, examples below.
a
Transformed/contained value type.

Some example instances that you might want to rely on from g:

Alternative
Superposition functor.
  • How do individual items have a set of possible values?
  • How do those possible values collapse to form one optional value?
  • etc.
etc
There are a lot of other utilities for this type.

Synopsis

Constructors

points Source #

Arguments

:: (Functor f, Alternative g) 
=> (a -> Bool)

A predicate that indicates whether a point is occupied by its original value or vacant.

-> f a

The seed points with their values.

-> Compose f g a

The constructed SubZero value.

Turns a container of values to a container of either retained or destroyed values based on a predicate

The type constraint allows us to model possible outcomes so destroyed values are just "no possible outcomes" while retained values represent "the only possible outcome".

To represent that "no value" is a possible outcome, a should be some type like (Maybe a) or (Either String a).

f
This Functor defines the broad scale behaviours but its Alternative instance is overridden. This in particular might change during upcoming design validation.
g
This Functor supplies the supercedent Alternative instance and thus the finer behaviours.

reveal Source #

Arguments

:: (Functor f, Applicative g) 
=> f a

Initial flat structure

-> Compose f g a

enhanced structure, albeit with no changes

Provides structure for values at the other end of a Functor

Destructors

flatten Source #

Arguments

:: Applicative f 
=> f a

Default values

-> Compose f Maybe a

Structured container

-> f a

Destructured container

If the type constructor of the possibilities concept is Maybe then you can use flatten to provide default values for impossible points.

  • NOTE: This uses the applicative instance of the broad scale Functor which means exact behaviour can vary depending on the type of Applicative f because each has a different technique to ensure a value is found for every point:

    list of a
    Cross-product; Providing all default values once for all points.
    ZipList a
    zipWith; Providing one default value for each point until there are either no defaults remaining or no more points.
    Identity a
    One default must surely be provided and it is used if a default is required.
    Maybe a
    Not sure exactly what this does, TBC.
    Either a
    Not sure exactly what this does, TBC.

Restructors

(<-$>) :: Functor f => (g a -> h a) -> Compose f g a -> Compose f h a Source #

fmap below the zeropoint

universal :: Functor f => (g a -> h a) -> Compose * * f g a -> Compose * * f h a Source #

fmap below the zeropoint, function variant of <-$> operator

(<-|>) :: (Applicative f, Alternative g) => Compose * * f g a -> Compose * * f g a -> Compose * * f g a Source #

Alternative below the zeropoint

class (Applicative g, Applicative h) => Superposition g h where Source #

collapse f empty = simplify empty
collapse f (pure x) = simplify (pure x)
collapse f (x <|> y) = pure (f x y)

g must form a monoid under f when empty is the monoid's identity.

Minimal complete definition

simplify, collapse

Methods

simplify :: g a -> Maybe (h a) Source #

Tries to convert from one alternative to another

collapse :: (a -> a -> a) -> g a -> h a Source #

Combines many alternatives into one using a function parameter. empty stays empty. This is quite free in the type of the result so the user can choose whether to keep the same type to re-expand the structure or to transform to a smaller type to avoid relying on instances for certain behaviours.

Instances

Alternative h => Superposition [] h Source #

Superposition within a nondeterminism list (ie, []) This is roughly the same as Superposition (Compose Identity []) h but of course they have different instances of other typeclasses and if that were really true then it would be Superpositions of Identity all the way down.

Methods

simplify :: [a] -> Maybe (h a) Source #

collapse :: (a -> a -> a) -> [a] -> h a Source #

(Applicative f, Superposition g h) => Superposition (Compose * * f g) (Compose * * f h) Source #

Superposition within Compose * g

Methods

simplify :: Compose * * f g a -> Maybe (Compose * * f h a) Source #

collapse :: (a -> a -> a) -> Compose * * f g a -> Compose * * f h a Source #

simplify :: Superposition g h => g a -> Maybe (h a) Source #

Tries to convert from one alternative to another

collapse :: Superposition g h => (a -> a -> a) -> g a -> h a Source #

Combines many alternatives into one using a function parameter. empty stays empty. This is quite free in the type of the result so the user can choose whether to keep the same type to re-expand the structure or to transform to a smaller type to avoid relying on instances for certain behaviours.

Instructors

keep :: Alternative f => (a -> Bool) -> a -> f a Source #

Turns a value "a" to Just a or Nothing based on a predicate assuming you use it in a context that wants Maybe a instead of some other representation of Alternatives

keepIdentity :: Alternative f => (a -> Bool) -> Identity a -> f a Source #

Does the same as keep for values at the other end of Identity.

keep = (keepIdentity . Identity) f