What do normal distributions, finite automata, hash tables, arbitrary predicates, strings, convex hulls, affine transformations, configuration files, and CSS styles have in common? And what are the integers, Haskell types, arbitrary graphs, alternative functors, matrices, regular expressions, and statistical samples? Finally, is it possible to somehow interconnect boolean algebra, electrical circuits, rectangular tables, thermal insulation of pipes or buildings, and images on a plane? There are two important answers to these questions: 1) programmers work with all these objects, 2) these objects have a similar algebraic structure : the first are monoids, the second are semirings, and the third are de Morgan algebras.
If we, programmers, learn ourselves and teach a computer to work with monoids, half rings and other structures, then it will become easier for all of us to work. Because certain constraints are imposed on algebraic structures, and certain guarantees follow from limitations. All these restrictions and guarantees are valid for all representatives of the structure, which means that you can build universal tools for working with monoids, semirings, algebras and, therefore, with all of the above and many other objects. See how many mathematicians defined algebraic structures! And after all, there are theorems for them, some useful for programmers, some not yet very good, but all of them are reliable, like the best program libraries!
Everything becomes even tastier when homomorphisms are built inside the structure — transformations that preserve the structure. Homomorphisms make it possible to "switch" from one structure object to another - from lists to numbers, from graphs to matrices, from regular expressions to graphs, from electrical circuits to boolean expressions or to graphical representations of these circuits! But isomorphisms are a song in general! If a programmer believes that he does not need mathematics and that all these morphism-morphisms are just abstract nonsense, then he deprives himself of not only an excellent, reliable tool, but, most importantly, an essential part of the pleasure of his work.
In this article, we will show, using the example of de Morgan algebras, how to construct algebraic abstractions, how to define homomorphisms and free algebras for them, and how this can be used, of course.
The article is intended for those who already know what type classes are, functors, monoids and, in general, are well aware of what Haskell programming is. On the other hand, it may be of interest to anyone who is interested in how abstractions are built in programming, and how they can be applied to real problems.
Monoids are an abstraction of composition. In turn, composition is a key concept in functional programming. That is why monoids are found here so often and play such important roles. Much has been said and written about the value and richness of using monoids. Here we list their main properties, which will be useful to us in the further presentation.
A monoid is a very simple structure: this is a set on which an associative binary operation is defined that has a single neutral element. The commutativity of the operation is not required, but the neutral element must be neutral, being both the first and second operand.
In the Haskell language for monoids, the class Monoid
:
class Monoid a where mempty :: a mappend :: a -> a -> a
and the Data.Monoid
library provides a number of useful instances of this class, such as Sum
, Product
, First
, Last
, Endo
, etc.
The key properties of a monoid are the associativity and uniqueness of the neutral element. These restrictions allow us to generalize monoidal operations for an arbitrary order of execution (including for parallel).
For any monoid, one can define a dual monoid in which the binary operation takes the arguments in the reverse order:
> Dual [1,2,3] <> Dual [5,6] Dual { getDual = [5,6,1,2,3] }
It is well known how a useful and versatile tool is convolution: on the one hand, dozens of useful universal functions that process collections are expressed through convolution, and on the other, lists, trees, and other inductive collections can be collapsed. The package is defined quite a lot. You can collapse the collection both on the right and on the left; this can affect the result (depending on the associativity of the folding function) and the efficiency of the calculations. You can collapse by entering the initial result of the convolution, in case of an empty collection, or doing without it, if there is a guarantee that the collection is not empty. Therefore, in the Haskell standard library and the Data.Foldable
library Data.Foldable
so many different convolutions:
foldr, foldl, foldr1, foldl1, foldl', foldl1'
If we are talking about a convolution into a monoid, one function is enough, due to the associativity of the monoidal operation and the guarantee of the presence of a neutral element.
fold :: (Monoid m, Foldable t) => tm -> m
The most commonly used option is to explicitly specify which monoid should be used for the convolution:
foldMap :: (Monoid m, Foldable t) => (a -> m) -> ta -> m
If the collection is a functor, the definition of the function foldMap
can be given as follows:
foldMap f = fold . fmap f
Sometimes it is possible to "move" between monoids, we recall, such transformations are called homomorphisms. Moreover, there exists a monoid from which one can construct a homomorphism into any other. Such a monoid is called free ; its role in Haskell is played by lists.
Free structures reflect the properties of an algebraic system, but do not “compute” anything, do not change data, and do not lose information. In a certain sense, they represent a formal language for describing an element of an algebraic system or category, while homomorphisms can be considered as interpreters of this language. This analogy will be useful to us in the future.
Read more about monoids and their use in Haskell can be found in the articles:
For many objects, there are several ways to compose and one cannot do without a single monoid. If there are two such methods, then they speak of rings, semirings, lattices, and various algebras. Let us consider several examples that suggest the generality of the algebraic structure underlying them.
What we know about Boolean algebra:
{True, False}
and is described using three operations: conjunction, disjunction, and negation.False
element is neutral for disjunction and absorbing for conjunction.True
is in turn a neutral element for conjunction and absorbing for disjunction.!(A wedgeB)=!A vee!B, quad!(A veeB)=!A wedge!B
Let's consider the problem of calculating an arbitrary bipolar electrical circuit, which may consist of resistances and allows for the series or parallel connection of circuit elements.
R1 leftrightarrowR2=R1+R2, quadR1 updownarrowR2= frac1 frac1R1+ frac1R2.
These expressions can be rewritten in a symmetric way:
frac1R1 updownarrowR2= frac1R1 leftrightarrow frac1R2, quad frac1R1 leftrightarrowR2= frac1R1 updownarrow frac1R2,
in which the laws of de Morgan are recognized!
Rectangular tables can also be combined in two main ways: combining rows ( leftrightarrow ) or columns ( updownarrow ):
1 2 3 ab 1 2 3 ab 4 5 6 <-> cd = 4 5 6 cd 7 8 9 ef 7 8 9 ef 1 2 3 abc 1 2 3 4 5 6 <|> def = 4 5 6 7 8 9 7 8 9 abc def
In addition, for tables, you can define an involution — transposition, and it is easy to check that both ways of combining tables form monoids with the same neutral element — an empty table. Finally, one combination method can be obtained from another: for example, you can merge two tables vertically by first transposing both tables, then merging them horizontally and transposing the result.
A leftrightarrowB=(A top updownarrowB top) top, quadA updownarrowB=(A top leftrightarrowB top) top.
Using the properties of involution, again we obtain the laws of de Morgan:
(A leftrightarrowB) top=A top updownarrowB top, quad(A updownarrowB) top=A top leftrightrowB top.
It is time to give a formal definition for the structure with which we work:
De Morgan's algebra is a structure consisting of a set on which two binary operations are defined. + and times , conditionally, called addition and multiplication, as well as the involution operation ′ for which the following conditions are true:
a+0=0+a=a, quada+(b+c)=(a+b)+c;
a times1=1 timesa=a,a times(b timesc)=(a timesb) timesc;
0 timesx=x times0=0;
(x′)′=x;
0′=1,1′=0;
(A+B)′=A′ timesB′,(A timesB)′=A′+B′.
Strictly speaking, multiplication must still be distributive with respect to addition, but in some cases (for example, for electrical circuits) this may not be done. But if it is done, then a complex expression consisting of a combination of additions and multiplications can be reduced to the form of the sum of monomials, opening all the brackets, or, conversely, simplifying the expression, putting the common factors behind the brackets.
Sometimes the involution plays the role of inversion, that is, it generates the inverse element for the multiplication operation. Then the following identity holds:
x timesx′=x′ timesx=1.
Before starting work, we will connect several extensions:
{-# LANGUAGE DeriveFunctor, FlexibleInstances, GeneralizedNewtypeDeriving #-}
We define a type class for de Morgan algebras:
class DeMorgan a where {-# MINIMAL inv,((<->)|(<|>)),(zero|one) #-} inv :: a -> a zero :: a zero = inv one one :: a one = inv zero (<->) :: a -> a -> a a <-> b = inv (inv a <|> inv b) (<|>) :: a -> a -> a a <|> b = inv (inv a <-> inv b)
In this definition, we already use the laws of de Morgan in order to simplify work with the class. In the description of an instance, it suffices to define only one of the two monoidal operations, its neutral element and involution.
Let's create the first instance of the DeMorgan
class for logical data:
instance DeMorgan Bool where zero = False inv = not (<->) = (&&)
For efficiency reasons, of course, it’s worth explicitly defining the <|>
operator, but we’ll leave this laconic definition to make sure that it fully defines the algebra for the Bool
type:
> True <|> False True > one :: Bool True
Boolean algebra is good, but it is painfully simple. Let us generalize it by constructing algebra for fuzzy logic in the spirit of Lotfi Zadeh. To do this, we define the Fuzzy
wrapper type and require the compiler to output numeric properties for it:
newtype Fuzzy = Fuzzy { deFuzzify :: Double } deriving (Show, Num, Fractional, Ord, Eq) instance DeMorgan Fuzzy where zero = 0 inv x = fuzzify $ 1 - x a <|> b = fuzzify $ max ab fuzzify x = 0 `max` x `min` 1
> deFuzzify $ one 1 > deFuzzify $ 0.2 <-> 0.4 0.2 > deFuzzify $ 0.8 <|> 0.4 <-> 0.5 0.5 > deFuzzify $ 0.3 <|> 0.4 <-> 0.5 0.4
Let us define the simplest de Morgan algebra for tables represented by nested lists:
instance DeMorgan [[a]] where zero = [] (<|>) = (++) inv = transpose
here we used the transpose
function from the Data.List
library. This is how this algebra works:
> inv [[1,2],[3,4]] [[1,3],[2,4]] > [[1,2],[3,4]] <-> [[5],[6]] [[1,2,5],[3,4,6]] > [[1,2],[3,4]] <|> [[5,6]] [[1,2],[3,4],[5,6]]
Let's apply it for writing a simple tabulation function table
table :: (Show a, Show b) => (a -> a -> b) -> [a] -> [[String]] table f vals = ([[" "]] <-> h) <|> (inv h <-> c) where h = [show <$> vals] c = [show <$> [ fxy | x <- vals] | y <- vals] showTable tbl = putStrLn $ unlines $ unwords <$> tbl
> showTable $ table mod [1..6] 1 2 3 4 5 6 1 0 0 0 0 0 0 2 1 0 1 0 1 0 3 1 2 0 1 2 0 4 1 2 3 0 1 2 5 1 2 3 4 0 1 6 1 2 3 4 5 0
Finally, recall the resistances and construct the de Morgan algebra for numbers, more precisely, for the numeric types for which the division operation is defined. To do this, define the type wrapper Frac
:
newtype Frac a = Frac {getFrac :: a} deriving (Show, Num, Fractional, Functor) instance Fractional a => DeMorgan (Frac a) where zero = 0 inv = (1/) (<->) = (+)
> getFrac $ 2 <-> 6 8.0 > getFrac $ 2 <|> 6 1.5 > getFrac $ 1 <-> (2 <|> (1 <-> 1)) 2.0
As an example, let us express the effective resistance of the circuit shown in the figure and calculate the current strength at a voltage of 12 V:
> getFrac $ ((6 <|> 12) <-> 4) <|> (3 <-> 5) 4.0 > getFrac $ 12 / ((6 <|> 12) <-> 4) <|> (3 <-> 5) 3.0
For calculating the effective stiffness of a complex spring system, or capacitor battery capacity, the type of Frac
also suitable, but for these calculations you need to swap the operators <|>
and <->
, as well as the elements zero
and one
. Mathematicians are happy to recognize in this transformation the transition to dual algebra. It sounds nice, but I would not like to write 2 <-> 3
, meaning parallel connection of springs. It would be good to keep the semantics of operators, but to change the way of calculations.
Here mathematics again gives us the opportunity to take advantage of its fruits. As for any monoid, for any de Morgan algebra, its dual algebra is defined, in which “the opposite is true”. We describe this circumstance in Haskell. Create a new type of wrapper Dual
for dual algebras and inform that if al is a de Morgan algebra, then the dual algebra will also be a de Morgan algebra.
newtype Dual a = Dual {getDual :: a} deriving (Show, Num, Fractional, Eq, Ord, Functor) instance DeMorgan a => DeMorgan (Dual a) where zero = Dual one one = Dual zero inv x = inv <$> x Dual a <|> Dual b = Dual $ a <-> b Dual a <-> Dual b = Dual $ a <|> b
Now you can calculate the effective stiffness of the system of three springs, one of which is connected in series with a pair of others connected in parallel:
> getFrac . getDual $ 600 <-> (200 <|> 300) 450.0
Type inference allows us to specify which kind of algebra we use only "at the output" of the calculations. So we can explicitly and, at the same time, simply, change the way the expression is evaluated.
But what if we want to represent and count circuits containing not only resistances, but also keys, capacitors, coils, etc.? And not only to count, but also to depict them or save to a file? For this we need free algebra.
The chain will be represented by some data structure, which does not calculate anything, but reflects the algebraic structure of the chain and the generator of the de Morgan algebra:
data Circuit a = Zero | One | Elem a | Inv (Circuit a) | Par (Circuit a) (Circuit a) | Seq (Circuit a) (Circuit a) deriving (Show, Functor)</hs></pre> instance DeMorgan (Circuit a) where zero = Zero one = One (<->) = Seq (<|>) = Par inv = Inv
Involution or inversion for a chain element has no definite meaning, but for correctness and generality, we included it in the type description.
The first and the most natural homomorphism is the transformation of the Circuit
type into an arbitrary type for which the de Morgan algebra is defined:
reduce :: DeMorgan a => Circuit a -> a reduce circ = case circ of Zero -> zero One -> one Elem b -> b Inv a -> inv (reduce a) Par ab -> reduce a <|> reduce b Seq ab -> reduce a <-> reduce b
The reduce
function is similar to the fold
function, which collapses the list of monoids into an arbitrary monoid. In the same way as from the function fold
for functors, you can produce the function foldMap
, you can form the function reduceMap
:
reduceMap :: DeMorgan b => (a -> b) -> Circuit a -> b reduceMap = reduce . fmap f
This function allows you to explicitly specify which de Morgan algebra should be used when interpreting a chain.
Agree, the discovery of such beautiful symmetry in the definitions of convolution functions for monoids and our algebra is aesthetic pleasure!
To build the circuits, we organize the object-oriented type Lumped
, which allows us, in addition to the values ​​of the parameters of the elements of the Value a
circuit, to clearly present the Short circuit and the Break
circuit break:
data Lumped a = Short | Value a | Break deriving (Show, Functor) instance DeMorgan s => DeMorgan (Lumped s) where zero = Break Value r1 <-> Value r2 = Value $ r1 <-> r2 Short <-> r = r r <-> Short = r _ <-> Break = Break Break <-> _ = Break inv Short = Break inv Break = Short inv (Value r) = Value (inv r)
We introduce a type for the elements: resistances, capacitances and inductances, as well as the designers of the elements of the circuit:
data Element = R Double | C Double | L Double deriving Show res = Elem . R cap = Elem . C coil = Elem . L key True = Zero key False = One
Finally, we write a simple chain for the experiments.
s :: Bool -> Circuit Element sk = res 10 <-> ((res 2 <-> coil 5e-3 <-> key k) <|> cap 10e-9)
Now we are ready to build various interpretations of our free algebra.
The connect
function determines whether a chain is closed using a Boolean algebra:
connected :: Circuit Element -> Bool connected = reduceMap f where f el = case el of R _ -> True C _ -> False L _ -> True
> connected (s True) True > connected (s False) False
The resistance
function determines the effective resistance of a circuit for direct current, using algebra for fractional numbers:
resistance :: Circuit Element -> Lumped Double resistance = fmap getFrac . reduceMap (fmap Frac . f) where f el = case el of R r -> Value r C _ -> Break L _ -> Short
Here the computational work is performed inside the type Lumped
, which we have declared to be a functor.
> resistance (s True) Value 12 > resistance (s False) Break
To calculate the circuit impedance, you need to connect the Data.Complex
module:
impedance :: Double -> Circuit Element -> Lumped (Complex Double) impedance w = fmap getFrac . reduceMap (fmap Frac . f) where f el = Value $ case el of R r -> r :+ 0 C c -> 1 / (0 :+ w*c) L l -> 0 :+ w*l
> impedance 1e3 (s False) Value (10.0 :+ (-99999.99999999997)) > impedance 1e3 (s True) Value (12.00020001420084 :+ 5.0002100065000405) > impedance 1e6 (s False) Value (10.0 :+ (-100.0)) > impedance 1e6 (s True) Value (10.000832986116954 :+ (-102.04081598653629))
If we are talking about the calculation of the capacitor bank, then we need to change the dual algebra:
capacity :: Circuit Element -> Lumped Double capacity = fmap (getFrac . getDual) . reduceMap (fmap (Dual . Frac) . f) where f el = case el of R _ -> Short C c -> Value c L _ -> Short
Notice how in all these interpretations we indicated the method of calculating the characteristics of the chain, defining only the method of calculation for the individual elements and choosing the appropriate algebra for the convolution.
And if we need to portray the chain, then you can use the magnificent Diagrams library to build vector graphics. It provides two combinators for the relative position of the images: (|||)
- side by side horizontally and (===)
- side by side vertically. This means that for images one can construct an algebra similar to the algebra of tables, and then, having described how the individual elements of the chain are depicted, construct a homomorphism from free algebra to image algebra and draw an arbitrary scheme. By the way, if you want to see the filigree and nontrivial use of monoids, pay attention to this library and to the articles related to it.
We have not considered all the possibilities offered by the use of abstraction for de Morgan algebra. It was possible to give an example of calculating the insulation of a building with windows and complex wall covering; or modeling of non-Newtonian fluids with chains of stiffness and viscosity elements.
For monoids and de Morgan algebra, a series of simple theorems holds; for example, it is known that the product of monoid types also forms a monoid. The equivalent statement is true for de Morgan algebras; it makes it possible to calculate several characteristics at once in a single pass through the structure. Moreover, it is easy to construct an epimorphism for an algebra into a monoid and calculate not only algebraic characteristics, but also any monoidal ones. As the simplest example: simultaneously with the calculation of resistances, it is possible to calculate the total power released by a chain, which will be described by a simple summing monoid.
Free algebra gives another possibility, essential, for example, for fuzzy logic problems. An expression that is not yet computed can be simplified if we use the distributivity of algebra. This procedure can be performed during program execution, that is, with arbitrary data, but before intensive calculations. What free structures are capable of showing Wolfram Mathematica, in which all expressions are essentially free algebras.
Compared to a horse or a car, the train has a significant limitation - it can only move by rail. And the railway has a significant limitation - only trains can move on it. But these restrictions provide new opportunities - it is possible to significantly reduce friction, increase speed and build a complex and effective automatic control system for the movement of hundreds of trains. On the highway you can not ride a moped or on a tractor. This is a limitation. But if we guarantee it, we can count on high speeds and high bandwidth of the route.
Functional programming adds various restrictions and laws to the programmer’s daily practice. The state cannot be changed, the composition must be associative, applicative functors and monads must satisfy the laws of applicative functors and monads, etc. This may be annoying, but along with these restrictions and laws come guarantees that the code will work that way and not otherwise. And most importantly, it is precisely the strict observance of these laws, in principle, that allows us to talk in the program about functors, monads, associativity and distributivity, algebras and other categories, and therefore use the achievements of many generations of mathematicians and apply them in daily work. So all these complex things are not crutches of the OP, as it may seem, but new features that have become available due to the development of the hardware of computers. Do not neglect them.
Source: https://habr.com/ru/post/323832/
All Articles