Relational Algebra library: first version on GitHub

Hello, A couple of weeks ago I asked if there was interest in a library that implements a type-safe relational algebra. The response was positive, so I have spruced up the code I had a bit and created a repository on GitHub at: https://github.com/PaulVisschers/relational-algebra It is a very rudimentary version. The code is not documented and there is only a very basic example database in Test.hs. It might be helpful to look at HaskellDB's PrimQuery and PrimExpr, as this library is mostly a direct copy from that (but typed). I will add some decent examples of expressions and queries shortly. If you check it out, please comment on it and let me know if you want to contribute. Since this is going to be my first release, any feedback is welcome. Paul Visschers

Hello there Paul,
Paul Visschers
A couple of weeks ago I asked if there was interest in a library that implements a type-safe relational algebra. The response was positive, so I have spruced up the code I had a bit and created a repository on GitHub at:
https://github.com/PaulVisschers/relational-algebra
It is a very rudimentary version. The code is not documented and there is only a very basic example database in Test.hs. It might be helpful to look at HaskellDB's PrimQuery and PrimExpr, as this library is mostly a direct copy from that (but typed). I will add some decent examples of expressions and queries shortly.
If you check it out, please comment on it and let me know if you want to contribute. Since this is going to be my first release, any feedback is welcome.
Well, the demonstration could be a bit more comprehensive. I would be very interested in seeing queries, especially nontrivial ones with joins and such. Would you mind writing a more comprehensive demonstration? Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

Hey Ertugrul,
You are absolutely right and the first item on my todo list is to add
better examples.
Paul
On Sun, Jul 22, 2012 at 5:24 AM, Ertugrul Söylemez
Hello there Paul,
Paul Visschers
wrote: A couple of weeks ago I asked if there was interest in a library that implements a type-safe relational algebra. The response was positive, so I have spruced up the code I had a bit and created a repository on GitHub at:
https://github.com/PaulVisschers/relational-algebra
It is a very rudimentary version. The code is not documented and there is only a very basic example database in Test.hs. It might be helpful to look at HaskellDB's PrimQuery and PrimExpr, as this library is mostly a direct copy from that (but typed). I will add some decent examples of expressions and queries shortly.
If you check it out, please comment on it and let me know if you want to contribute. Since this is going to be my first release, any feedback is welcome.
Well, the demonstration could be a bit more comprehensive. I would be very interested in seeing queries, especially nontrivial ones with joins and such.
Would you mind writing a more comprehensive demonstration?
Greets, Ertugrul
-- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Patrick Browne
{- Below is a *specification* of a queue. If possible I would like to write the equations in type class. Does the type class need two type variables? How do I represent the constructors? Can the equations be written in the type class rather than the instance? -}
(Side note: When opening a new topic, please don't /reply/ to a post, but post it separately by creating a new mail.) The type class needs to know the element type, so your observation is correct. Usually, as in your case, the element type follows from the data structure type, and you will want to inform the type system about this connection. There are basically three ways to do it. The first is using MultiParamTypeClasses and FunctionalDependencies: class Stacklike a s | s -> a where empty :: s a null :: s a -> Bool push :: a -> s a -> s a pop :: s a -> Maybe a size :: s a -> Int tail :: s a -> Maybe (s a) Another way is using an associated type (TypeFamilies). This is cleaner, but much more noisy in the type signatures: class Stacklike s where type StackElement s empty :: s (StackElement s) null :: s (StackElement s) -> Bool push :: StackElement s -> s (StackElement s) -> s (StackElement s) pop :: s (StackElement s) -> Maybe (StackElement s) size :: s (StackElement s) -> Int tail :: s (StackElement s) -> Maybe (s (StackElement s)) Finally once you realize that there is really no need to fix the element type in the type class itself, you can simply write a type class for the type constructor, similar to how classes like Functor are defined: class Stacklike s where empty :: s a null :: s a -> Bool push :: a -> s a -> s a pop :: s a -> Maybe a size :: s a -> Int tail :: s a -> Maybe (s a) The big question is whether you want to write a class at all. Usually classes are used to capture patterns, not operations. Greets, Ertugrul -- Not to be or to be and (not to be or to be and (not to be or to be and (not to be or to be and ... that is the list monad.

Generally the way this is done in Haskell is that the interface to the type
is specified in a typeclass (or, alternatively, in a module export list,
for concrete types), and the axioms are specified in a method to be tested
in some framework (i.e. QuickCheck, SmallCheck, SmartCheck) which can
automatically generate instances of your type and test that the axioms hold.
For example:
class QueueLike q where
empty :: q a
insert :: a -> q a -> q a
viewFirst :: q a -> Maybe (a, q a)
size :: q a -> Integer
-- can use a single proxy type if have kind polymorphism, but that's an
experimental feature right now
data Proxy2 (q :: * -> *) = Proxy2
instance Arbitrary (Proxy2 q) where arbitrary = return Proxy2
prop_insertIncrementsSize :: forall q. QueueLike q => q () -> Bool
prop_insertIncrementsSize q = size (insert () q) == size q + 1
prop_emptyQueueIsEmpty :: forall q. QueueLike q => Proxy2 q => Bool
prop_emptyQueueIsEmpty Proxy2 = maybe True (const False) $ view (empty :: q
())
Then you specialize these properties to your type and test them:
instance QueueLike [] where ...
ghci> quickCheck (prop_insertIncrementsSize :: [()] -> Bool)
Valid, passed 100 tests
or
Failed with: [(), (), ()]
QuickCheck randomly generates objects of your data structure and tests your
property against them. While not as strong as a proof, programs with 100%
quickcheck coverage are *extremely* reliable. SmartCheck is an extension
of QuickCheck that tries to reduce test cases to the minimum failing size.
SmallCheck does exhaustive testing on the properties for finite data
structures up to a particular size. It's quite useful when you can prove
your algorithms 'generalize' after a particular point.
There aren't any libraries that I know of for dependent-type style program
proof for haskell; I'm not sure it's possible. The systems I know of have
you program in a more strongly typed language (Coq/agda) and export Haskell
programs once they are proven safe. Many of these rely on unsafeCoerce in
the Haskell code because they have proven stronger properties about the
types than Haskell can; I look at that code with some trepidation--I am not
sure what guarantees the compiler makes about unsafeCoerce.
-- ryan
On Sun, Jul 22, 2012 at 7:19 AM, Patrick Browne
{- Below is a *specification* of a queue. If possible I would like to write the equations in type class. Does the type class need two type variables? How do I represent the constructors? Can the equations be written in the type class rather than the instance? -}
module QUEUE_SPEC where data Queue e = New | Insert (Queue e) e deriving Show
isEmpty :: Queue e -> Bool isEmpty New = True isEmpty (Insert q e) = False
first :: Queue e -> e first (Insert q e) = if (isEmpty q) then e else (first q)
rest :: Queue e -> Queue e rest (Insert q e ) = if (isEmpty q) then New else (Insert (rest q) e)
size :: Queue e -> Int size New = 0 size (Insert q e) = succ (size q)
{- some tests of above code size (Insert (Insert (Insert New 5) 6) 3) rest (Insert (Insert (Insert New 5) 6) 3)
My first stab at a class class QUEUE_SPEC q e where new :: q e insert :: q e -> q e isEmpty :: q e -> Bool first :: q e -> e rest :: q e -> q e size :: q e -> Int
-}
Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán. http://www.dit.ie This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean. http://www.dit.ie _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Great / thanks!!! This will be incredibly helpful for some of my present work. :-) On Saturday, July 21, 2012, Paul Visschers wrote:
Hello,
A couple of weeks ago I asked if there was interest in a library that implements a type-safe relational algebra. The response was positive, so I have spruced up the code I had a bit and created a repository on GitHub at:
https://github.com/PaulVisschers/relational-algebra
It is a very rudimentary version. The code is not documented and there is only a very basic example database in Test.hs. It might be helpful to look at HaskellDB's PrimQuery and PrimExpr, as this library is mostly a direct copy from that (but typed). I will add some decent examples of expressions and queries shortly.
If you check it out, please comment on it and let me know if you want to contribute. Since this is going to be my first release, any feedback is welcome.
Paul Visschers
participants (5)
-
Carter Schonwald
-
Ertugrul Söylemez
-
Patrick Browne
-
Paul Visschers
-
Ryan Ingram