rec-def-0.1: Recusively defined values
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Recursive.Set

Description

The type R (Dual Bool) is ike Bool, but allows recursive definitions:

>>> :{
  let s1 = rInsert 23 s2
      s2 = rInsert 42 s1
  in getR s1
 :}
fromList [23,42]
Synopsis

Documentation

data R a Source #

A value of type R a is a a, but defined using only specific operations (which you will find in the corresponding module, e.g. Data.Recursive.Bool), which allow recursive definitions.

You can use getR to extract the value.

Do not use the extracted value in the definition of that value, this will loop just like a recursive definition with plain values would.

mkR :: HasPropagator a => a -> R a Source #

Any value of type a is also a value of type r a.

getR :: HasPropagator a => R a -> a Source #

Extract the value from a R a. This must not be used when _defining_ that value.

rEmpty :: Eq a => R (Set a) Source #

getR rEmpty === S.empty

rInsert :: Ord a => a -> R (Set a) -> R (Set a) Source #

getR (rInsert n r1) === S.insert n (getR r1)

rDelete :: Ord a => a -> R (Set a) -> R (Set a) Source #

getR (rDelete n r1) === S.delete n (getR r1)

rFilter :: Ord a => (a -> Bool) -> R (Set a) -> R (Set a) Source #

\(Fun _ p) -> getR (rFilter p r1) === S.filter p (getR r1)

rUnion :: Ord a => R (Set a) -> R (Set a) -> R (Set a) Source #

getR (rUnion r1 r2) === S.union (getR r1) (getR r2)

rUnions :: Ord a => [R (Set a)] -> R (Set a) Source #

getR (rUnions rs) === S.unions (map getR rs)

rIntersection :: Ord a => R (Set a) -> R (Set a) -> R (Set a) Source #

getR (rIntersection r1 r2) === S.intersection (getR r1) (getR r2)

rMember :: Ord a => a -> R (Set a) -> R Bool Source #

getR (rMember n r1) === S.member n (getR r1)

rNotMember :: Ord a => a -> R (Set a) -> R (Dual Bool) Source #

getRDual (rNotMember n r1) === S.notMember n (getR r1)

rDisjoint :: Ord a => R (Set a) -> R (Set a) -> R (Dual Bool) Source #

getRDual (rDisjoint r1 r2) === S.disjoint (getR r1) (getR r2)