shapely-data-0.1: Generics using @(,)@ and @Either@, with algebraic operations and typed conversions

Safe HaskellNone

Data.Shapely.Normal

Contents

Synopsis

Documentation

Functions for composing and modifying our Normal form types.

These take their names from the familiar functions in Data.List and Prelude, but are given more general forms, sometimes loosely after the constructions in Edward Kmett's categories package. There are probably many improvements and additions possible here.

You probably want to import this in one of the following ways:

 import Data.Shapely.Normal as Sh
 import qualified Data.Shapely.Normal as Sh
 import Data.Shapely.Normal hiding ((!!),repeat,replicate,concat,reverse, map, length)

NOTE: The structure of the classes, type functions, and class constraints here are likely to change a lot.

newtype Only a Source

A singleton inhabited Sum. This is an intermediate type useful for constructing sums, and in our instances (see e.g. Tail)

Constructors

Only 

Fields

just :: a
 

Instances

~ Bool false False => HasAny p (Only x) false 
HasAny p (Only p) True 
Eq a => Eq (Only a) 
Ord a => Ord (Only a) 
Read a => Read (Only a) 
Show a => Show (Only a) 
Product t => Sum (Only t) 
Exponent a => Exponent (Only a) 

Reordering Product and Sum terms

class Reversable t whereSource

Reversing Products and Sums

Associated Types

type Reversed t Source

Methods

reverse :: t -> Reversed tSource

Instances

Reversable () 
(~ * xs (Either y zs), ~ * (Reversed (Either x xs)) (ShiftedL (Either x (Reversed xs))), Reversable xs, Shiftable (Either x (Reversed xs))) => Reversable (Either x (Either y zs)) 
Reversable (Either x (a, b)) 
Reversable (Either x ()) 
(Reversable xs, Shiftable (x, Reversed xs)) => Reversable (x, xs) 

class Shiftable t whereSource

a class for shifting a sum or product left or right by one element, i.e. a logical shift

Methods

shiftl :: t -> ShiftedL tSource

shiftr :: t -> ShiftedR tSource

Instances

(Shiftable (Either y zs), Shiftable (Either x zs), ~ * xs (Either y zs), ~ * (Tail (Either x zs)) (Tail xs), ~ * (:< (Last xs) (:< x (Init xs))) (Either a0 (Either x c0)), ~ * (:< (Last xs) (Init xs)) (Either a0 c0)) => Shiftable (Either x (Either y zs)) 
Shiftable (Either a (x, y)) 
Shiftable (Either a ()) 
(Shiftable (y, zs), Shiftable (x, zs), ~ * (ShiftedR (y, zs)) (Last (y, zs), Init (y, zs))) => Shiftable (x, (y, zs)) 
Shiftable (x, ()) 

viewr :: (Symmetric (->) p, Shiftable t, ShiftedR t ~ p a b) => t -> p b aSource

Note: viewl would be simply id.

 viewr = swap . shiftr

Convenience Type synonyms

type :*: = (,)Source

type :*! x y = (x, (y, ()))Source

Operations on Products

Homogeneous (list-like) products

class Product as => Homogeneous a as | as -> a whereSource

A class for homogeneous Products with terms all of type a.

Methods

repeat :: a -> asSource

Fill a product with an initial value. If the size of the resulting product can't be inferred from context, provide a sype signature:

 truths = repeat True :: (Bool,(Bool,(Bool,())))

An n-ary codiag. See also extract for Sums

toFList :: as -> FixedList (Length as) aSource

Convert a homogeneous product to a fixed-length list.

fromFList :: (as ~ Replicated len a, len ~ Length as) => FixedList len a -> Replicated len aSource

Convert a list back into a homogeneous Product.

Instances

Homogeneous a () 
(Homogeneous a as, ~ * (Replicated (Length as) a) as) => Homogeneous a (a, as) 

data FixedList length a Source

An opaque wrapper type allowing application of useful class methods on Homogeneous Products. Only operations that don't modify the length of the product (which is stored in the len parameter) are supported.

Instances

Functor (FixedList length) 
Foldable (FixedList length) 
Traversable (FixedList length) 
Eq a => Eq (FixedList length a) 
Ord a => Ord (FixedList length a) 
(~ * as (Replicated len a), Homogeneous a as, Show as, ~ * len (Length as)) => Show (FixedList len a) 

(!!) :: (Product as, as ~ (i :=>-> a), i ~ Length as, Exponent i) => as -> i -> aSource

Return the term at the 1-based index n of the Homogeneous Product xs.

 as !! i = 'fanin' as (i `'_of'` 'length' as)

($$:) :: (Length as ~ len, Replicated len b ~ bs, Homogeneous b bs, Homogeneous a as, Length bs ~ len) => (FixedList len a -> FixedList len b) -> as -> bsSource

 ($$:) f = fromFList . f . toFList

replicate :: (Homogeneous a as, as ~ Replicated len a, len ~ Length as) => Proxy len -> a -> Replicated len aSource

Replicate a, producing a Product of length len.

 replicate _ = 'repeat'

Construction convenience operators

single :: a -> (a, ())Source

(*:) :: Product xs => x -> xs -> (x, xs)Source

A left push for Products.

 (*:) = (,)

For a right push, see (>*).

(*!) :: x -> y -> (x, (y, ()))Source

Convenience function for combining Product terms, with (*:), e.g. 0 *: 1 *: 2 *! 3

 x *! y = (x,(y,()))

Forcing types

class (Product p, Length p ~ c) => HavingLength c p | c -> pSource

this inverts Length

Instances

HavingLength () (a, ()) 
(HavingLength c p, ~ * (Length (a, p)) (Either () c)) => HavingLength (Either () c) (a, p) 

ary :: HavingLength c p => Proxy c -> (p -> x) -> p -> xSource

 ary _ = id

Force the arity of an arity-polymorphic function on Products. e.g.

>>> :t _3 `ary` shiftl
_3 `ary` shiftl :: (a, (a1, (a2, ()))) -> ShiftedL (a, (a1, (a2, ())))

Product and Sum Conversions

class MassageableNormal x y whereSource

A class for massaging Normal representation types. This works as described in Massageable, except that it doesn't recurse into subterms.

Methods

massageNormal :: x -> ySource

Convert a Normal type x into some Massageable normal-form type y

Instances

MassageableNormalRec FLAT FLAT x y => MassageableNormal x y 

Algebraic

Factoring

extract :: (FactorPrefix t (Either t ts), Constant (Either t ts :/ t)) => Either t ts -> tSource

Factor out and return the Product from a homogeneous Sum. An n-ary codiag.

See also repeat for Products.

 extract = fst . factorPrefix

class Product ab => FactorPrefix ab abcs whereSource

A Product or Sum abcs out of which we can factor the product ab, leaving some quotient.

Associated Types

type abcs :/ ab Source

The quotient of ab factored from abcs

Methods

factorPrefix :: abcs -> (ab, abcs :/ ab)Source

Instances

FactorPrefix () () 
(FactorPrefix () abc, FactorPrefix () abcs) => FactorPrefix () (Either abc abcs) 
FactorPrefix () (x, y) 
(FactorPrefix (x, y) abc, FactorPrefix (x, y) abcs) => FactorPrefix (x, y) (Either abc abcs) 
FactorPrefix bs bcs => FactorPrefix (a, bs) (a, bcs) 

Distributing

class DistributeTerm xs whereSource

Algebraic multiplication of a term with some Normal type xs. When xs is a Product these are simple Cons/Snoc (see *:). For Sums the operation is distributed over all constructors, as in: a(x + y + z) = (ax + ay + az)

Methods

(*<) :: a -> xs -> a :*<: xsSource

prepend the term a.

(>*) :: xs -> a -> xs :>*: aSource

append the term a.

type family a :*<: xs Source

class Multiply xs ys whereSource

Algebraic multiplication of two Normal form types xs and ys. When both are Products this operation is like the Prelude (++). When both are Sums the ordering of constructors follow the "FOIL" pattern, e.g. (a + b + c)*(x + y) == (ax + ay + bx + by + cx + cy)

Just like normal multiplication, this is a monoid with () as our identity object.

Associated Types

type xs :>*<: ys Source

Methods

(>*<) :: xs -> ys -> xs :>*<: ysSource

Multiply Normal types.

Instances

Multiply () ys 
(Multiply as ys, Multiply bss ys, Concatable (Either (:>*<: as ys) (:>*<: bss ys))) => Multiply (Either as bss) ys 
(Product xs, DistributeTerm (:>*<: xs ys), Multiply xs ys) => Multiply (x, xs) ys 

Exponentiation

In the algebra of algebraic datatypes, (->) is analogous to exponentiation, where xᵇ == (b -> x). The operations here come from translating the algebraic laws of exponents to their equivalents on ADTs.

class Exponent abc whereSource

A class for the exponent laws with the Normal form abc in the exponent place. See the instance documentation for concrete types and examples.

Methods

fanin :: (abc :=>-> x) -> abc -> xSource

unfanin :: (abc -> x) -> abc :=>-> xSource

Instances

Exponent () 
Exponent a => Exponent (Only a) 
(EitherTail bs, Exponent bs, Exponent (AsTail bs), Exponent a) => Exponent (Either a bs)
fanin
an n-ary (|||) or either, (and (!!))
unfanin
an n-ary f :: (Either a b -> x) -> (a -> x, b -> x)

Examples:

>>> let s = Right $ Right (1,([2..5],())) :: Either (Int,()) ( Either () (Int,([Int],())) )
>>> fanin ((+1), (3, (foldr (+), ()))) s
15
Exponent bs => Exponent (a, bs)
fanin
an n-ary uncurry
unfanin
an n-ary curry

Examples:

>>> fanin (+) (1,(2,()))
3
>>> unfanin ('_4' `'ary'` ('shiftl' . 'reverse')) 1 2 3 4
(3,(2,(1,(4,()))))

type family abc :=>-> x Source

The algebraic normal form Exponent abc distributed over the single base variable x.

class Base abc whereSource

A class for the exponent laws with the Normal form abc in the base place. See the instance documentation for concrete types and examples.

Methods

fanout :: (x :->=> abc) -> x -> abcSource

unfanout :: (x -> abc) -> x :->=> abcSource

Instances

Base () 
Base bs => Base (a, bs)
fanout
an n-ary (&&&)
unfanout
an n-ary f :: (x -> (a,b)) -> (x -> a, x -> b)

Examples:

>>> fanout (head,(tail,())) [1..3] == (1,([2,3],()))
True

type family x :->=> abc Source

The single exponent variable x distributed over the algebraic normal form Base abc.

constructorsOfNormal :: Exponent r => r -> r :=>-> rSource

 constructorsOfNormal = 'unfanin' id

See also constructorsOf. E.g.

 constructorsOfNormal ('a',('b',())) 'x' 'y'  ==  ('x',('y',()))

Constants

class Constant c Source

Sums of the unit type are our constants in the algebra of ADTs. They are cardinal numbers at the type level (length), while their values are ordinal numbers (indicating position).

Instances

Constant () 
Constant c => Constant (Either () c) 

type family Length t Source

type family Replicated len a Source

Cardinals

type One = ()Source

Ordinals

class Constant c => OneOrMore c whereSource

Methods

_1st :: cSource

Instances

Forcing types

length :: Product as => as -> Proxy (Length as)Source

_of :: c -> Proxy c -> cSource

Used as in e.g. _3rd _of _7, which has inferred type Seven.