Copyright | © Thor Michael Støre, 2015 |
---|---|
License | GPL v2 without "any later version" clause |
Maintainer | thormichael át gmail døt com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Relational assignment and specalizations thereof. As with Database.HaskRel.Relational.Algebra this does not support relational expressions building on relvars, but defers that to Database.HaskRel.Relational.Expression.
- assign :: (Ord (HList a), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) r a, HLabelSet (LabelsOf a), SameLength' r a, SameLength' r (LabelsOf a), SameLength' a r, SameLength' (LabelsOf a) r) => Relvar a -> Relation r -> IO ()
- insert :: (Ord (HList a), Read (HList (RecordValuesR a)), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) r a, HLabelSet (LabelsOf a), HMapAux HList TaggedFn (RecordValuesR a) a, SameLength' r a, SameLength' r (LabelsOf a), SameLength' a r, SameLength' (LabelsOf a) r) => Relvar a -> Relation r -> IO ()
- dInsert :: (Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR r)), Typeable t, RecordValues r, RecordValues t, HRearrange3 (LabelsOf t) r t, HLabelSet (LabelsOf t), HMapAux HList TaggedFn (RecordValuesR t) t, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR t) [[String]], SameLength' r t, SameLength' r (LabelsOf t), SameLength' t r, SameLength' (LabelsOf t) r) => Relvar t -> Relation r -> IO ()
- update :: (Ord (HList a), Read (HList (RecordValuesR a)), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) (HAppendListR r r'2) a, HLabelSet (LabelsOf a), HLabelSet (LabelsOf (HAppendListR r r'2)), HDeleteLabels (LabelsOf r) a r'2, HMapAux HList TaggedFn (RecordValuesR a) a, HAppendList r r'2, SameLength' a (HAppendListR r r'2), SameLength' (LabelsOf a) (HAppendListR r r'2), SameLength' (HAppendListR r r'2) a, SameLength' (HAppendListR r r'2) (LabelsOf a), HAllTaggedLV (HAppendListR r r'2)) => Relvar a -> (Record a -> Bool) -> (Record a -> Record r) -> IO ()
- updateAll :: (Ord (HList a), Read (HList (RecordValuesR a)), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) (HAppendListR r r'2) a, HLabelSet (LabelsOf a), HLabelSet (LabelsOf (HAppendListR r r'2)), HDeleteLabels (LabelsOf r) a r'2, HMapAux HList TaggedFn (RecordValuesR a) a, HAppendList r r'2, SameLength' a (HAppendListR r r'2), SameLength' (LabelsOf a) (HAppendListR r r'2), SameLength' (HAppendListR r r'2) a, SameLength' (HAppendListR r r'2) (LabelsOf a), HAllTaggedLV (HAppendListR r r'2)) => Relvar a -> (Record a -> Record r) -> IO ()
- delete :: (Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR t)), RecordValues t, HMapAux HList TaggedFn (RecordValuesR t) t) => Relvar t -> Relation t -> IO ()
- iDelete :: (Ord (HList a), Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR t)), Typeable a, RecordValues a, RecordValues t, HRearrange3 (LabelsOf t) a t, HRearrange3 (LabelsOf a) t a, HLabelSet (LabelsOf t), HLabelSet (LabelsOf a), HMapAux HList TaggedFn (RecordValuesR t) t, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]], SameLength' a t, SameLength' a (LabelsOf t), SameLength' t a, SameLength' t (LabelsOf a), SameLength' (LabelsOf t) a, SameLength' (LabelsOf a) t) => Relvar t -> Relation a -> IO ()
- deleteP :: (Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR t)), RecordValues t, HMapAux HList TaggedFn (RecordValuesR t) t) => Relvar t -> (RTuple t -> Bool) -> IO ()
- updateA :: (Ord (HList r), Read (HList (RecordValuesR r)), Show (HList (RecordValuesR r)), HUpdateAtLabel2 k l v r r, RecordValues r, HasField k l (Record r) v, HMapAux HList TaggedFn (RecordValuesR r) r, SameLength' * * r r) => Relvar r -> (Record r -> Bool) -> (Record r -> Tagged k l v) -> IO ()
- updateAllA :: (Ord (HList r), Read (HList (RecordValuesR r)), Show (HList (RecordValuesR r)), HUpdateAtLabel2 k l v r r, RecordValues r, HasField k l (Record r) v, HMapAux HList TaggedFn (RecordValuesR r) r, SameLength' * * r r) => Relvar r -> (Record r -> Tagged k l v) -> IO ()
The primitive assignment function
assign :: (Ord (HList a), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) r a, HLabelSet (LabelsOf a), SameLength' r a, SameLength' r (LabelsOf a), SameLength' a r, SameLength' (LabelsOf a) r) => Relvar a -> Relation r -> IO () Source
Writes a relation value to a relvar file, replacing the existing value.
Specialized assignment functions
insert :: (Ord (HList a), Read (HList (RecordValuesR a)), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) r a, HLabelSet (LabelsOf a), HMapAux HList TaggedFn (RecordValuesR a) a, SameLength' r a, SameLength' r (LabelsOf a), SameLength' a r, SameLength' (LabelsOf a) r) => Relvar a -> Relation r -> IO () Source
Inserts a relation into a relvar. This differs from SQL's INSERT; the relvar is updated to the union of the relvar and the relation value given as arguments.
See insert
.
dInsert :: (Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR r)), Typeable t, RecordValues r, RecordValues t, HRearrange3 (LabelsOf t) r t, HLabelSet (LabelsOf t), HMapAux HList TaggedFn (RecordValuesR t) t, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR t) [[String]], SameLength' r t, SameLength' r (LabelsOf t), SameLength' t r, SameLength' (LabelsOf t) r) => Relvar t -> Relation r -> IO () Source
Disjoint insert. Closer to SQL INSERT, except that this will never insert a duplicate tuple.
See dInsert
.
update :: (Ord (HList a), Read (HList (RecordValuesR a)), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) (HAppendListR r r'2) a, HLabelSet (LabelsOf a), HLabelSet (LabelsOf (HAppendListR r r'2)), HDeleteLabels (LabelsOf r) a r'2, HMapAux HList TaggedFn (RecordValuesR a) a, HAppendList r r'2, SameLength' a (HAppendListR r r'2), SameLength' (LabelsOf a) (HAppendListR r r'2), SameLength' (HAppendListR r r'2) a, SameLength' (HAppendListR r r'2) (LabelsOf a), HAllTaggedLV (HAppendListR r r'2)) => Relvar a -> (Record a -> Bool) -> (Record a -> Record r) -> IO () Source
Updates tuples of a relvar that match the given predicate. As SQL UPDATE.
>>>
update sp (\ [pun|pno|] -> pno == "P2" || pno == "P3" ) (\ [pun|qty|] -> _qty ( qty - 25 ) .*. emptyRecord)
Updated 5 of 12 tuples in SuppliersPartsDB/SP.rv *SuppliersPartsExample> rPrint$ sp ┌─────┬─────┬─────┐ │ sno │ pno │ qty │ ╞═════╪═════╪═════╡ │ S1 │ P1 │ 300 │ │ S1 │ P2 │ 175 │ │ S1 │ P3 │ 375 │ │ S1 │ P4 │ 200 │ ...
Note how the cardinality of the relvar will be equal or lower after an update:
>>>
assign sp sp'
Value assigned to SuppliersPartsDB/SP.rv>>>
count sp
12>>>
update sp (\[pun|pno|] -> pno == "P1" || pno == "P2" || pno == "P3") (\_ -> _pno "P1" .*. _qty 50 .*. emptyRecord)
Updated 7 of 12 tuples in SuppliersPartsDB/SP.rv>>>
count sp
9
updateAll :: (Ord (HList a), Read (HList (RecordValuesR a)), Show (HList (RecordValuesR a)), RecordValues a, HRearrange3 (LabelsOf a) (HAppendListR r r'2) a, HLabelSet (LabelsOf a), HLabelSet (LabelsOf (HAppendListR r r'2)), HDeleteLabels (LabelsOf r) a r'2, HMapAux HList TaggedFn (RecordValuesR a) a, HAppendList r r'2, SameLength' a (HAppendListR r r'2), SameLength' (LabelsOf a) (HAppendListR r r'2), SameLength' (HAppendListR r r'2) a, SameLength' (HAppendListR r r'2) (LabelsOf a), HAllTaggedLV (HAppendListR r r'2)) => Relvar a -> (Record a -> Record r) -> IO () Source
Updates tuples of a relvar that match the given predicate.
In SQL and Tutorial D both the predicate of UPDATE
is an optional clause, but optional clauses isn't idiomatic Haskell, hence this separate updateAll function.
>>>
updateAll sp (\ [pun|qty pno|] -> _qty ( qty - 25 ) .*. _pno ( pno ++ "X" ) .*. emptyRecord)
Updated 12 tuples in SuppliersPartsDB/SP.rv *SuppliersPartsExample> pt sp ┌───────────────┬───────────────┬────────────────┐ │ sno :: String │ pno :: String │ qty :: Integer │ ╞═══════════════╪═══════════════╪════════════════╡ │ S1 │ P1X │ 275 │ ...
delete :: (Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR t)), RecordValues t, HMapAux HList TaggedFn (RecordValuesR t) t) => Relvar t -> Relation t -> IO () Source
Deletes a specified subset of a relvar. Note that this is not SQL DELETE, but instead a generalization thereof.
See delete
.
iDelete :: (Ord (HList a), Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR t)), Typeable a, RecordValues a, RecordValues t, HRearrange3 (LabelsOf t) a t, HRearrange3 (LabelsOf a) t a, HLabelSet (LabelsOf t), HLabelSet (LabelsOf a), HMapAux HList TaggedFn (RecordValuesR t) t, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]], SameLength' a t, SameLength' a (LabelsOf t), SameLength' t a, SameLength' t (LabelsOf a), SameLength' (LabelsOf t) a, SameLength' (LabelsOf a) t) => Relvar t -> Relation a -> IO () Source
Performs an inclusive delete against a relvar. Also not SQL DELETE. This will fail if the second argument is not a subset of the relation value identified by the relation variable reference.
See iDelete
.
deleteP :: (Ord (HList t), Read (HList (RecordValuesR t)), Show (HList (RecordValuesR t)), RecordValues t, HMapAux HList TaggedFn (RecordValuesR t) t) => Relvar t -> (RTuple t -> Bool) -> IO () Source
Delete by predicate, as SQL DELETE.
>>>
let newProd = relation [rTuple (pno .=. "P7", pName .=. "Baloon", color .=. "Red", weight .=. (-5 :: Rational), city .=. "Berlin")]
>>>
insert p newProd
Inserted 1 of 1 tuples into SuppliersPartsDB/P.rv>>>
deleteP p (\ [pun|pno|] -> pno == "P7" )
Deleted 1 tuples from SuppliersPartsDB/P.rv
Further specialized and simplified forms of update
updateA :: (Ord (HList r), Read (HList (RecordValuesR r)), Show (HList (RecordValuesR r)), HUpdateAtLabel2 k l v r r, RecordValues r, HasField k l (Record r) v, HMapAux HList TaggedFn (RecordValuesR r) r, SameLength' * * r r) => Relvar r -> (Record r -> Bool) -> (Record r -> Tagged k l v) -> IO () Source
Updates all tuples of a relvar. The second argument is a function that results in an attribute, making for a simpler function than for update
.
>>>
updateA sp (\ [pun|pno|] -> pno == "P2" || pno == "P3" ) (\ [pun|qty|] -> _qty $ qty - 25)
Updated 5 of 12 tuples in SuppliersPartsDB/SP.rv
updateAllA :: (Ord (HList r), Read (HList (RecordValuesR r)), Show (HList (RecordValuesR r)), HUpdateAtLabel2 k l v r r, RecordValues r, HasField k l (Record r) v, HMapAux HList TaggedFn (RecordValuesR r) r, SameLength' * * r r) => Relvar r -> (Record r -> Tagged k l v) -> IO () Source
Updates all tuples of a relvar. The second argument is a function that results in an attribute, making for a simpler function than for updateAll
.
>>>
updateAllA sp (\ [pun|qty|] -> _qty $ qty - 50)
Updated 12 tuples in SuppliersPartsDB/SP.rv>>>
rPrint$ sp
┌───────────────┬───────────────┬────────────────┐ │ sno :: String │ pno :: String │ qty :: Integer │ ╞═══════════════╪═══════════════╪════════════════╡ │ S1 │ P1 │ 250 │ ...