[Haskell] ANN: HaskRel; Employing GHC as a DBMS with support for the relational algebra

Jeremy Shaw jeremy at n-heptane.com
Thu Dec 31 19:23:56 UTC 2015


Would it be feasible to use this in conjunction with [acid-state](
http://acid-state.seize.it/) to create a more complete RDBMS?

- jeremy

On Sun, Nov 22, 2015 at 7:22 PM, Thor Michael Støre <thormichael at gmail.com>
wrote:

> Hello,
>
> After much scratching of my head over intricate parts of this "Haskell"
> thing
> I'm happy to announce that I've finally released my first effort in it:
> HaskRel.
>
> Overview
> --------
>
> Because I've spent quite a bit of time on database prompts I thought it
> would be
> a fun exercise to see how much GHC can be made to operate like a DBMS, and
> how
> much of the relational model of database management (as defined by Chris
> Date et
> al. today) I'm able to make it accommodate. I'm pleased to register that
> the
> relational algebra, base variables and assignment works as one would
> expect at a
> database prompt. It does not qualify as an actual *RDBMS*
> (unsurprisingly),
> since it doesn't implement many other things that are required for it to
> be a
> proper RDBMS, either because I haven't gotten around to it or they cannot
> be
> implemented in Haskell.
>
> I've put the source up on GitHub and published it on Hackage:
>
>   Hackage:
>   http://hackage.haskell.org/package/HaskRel
>
>   GitHub:
>   https://github.com/thormick/HaskRel/tree/master/HaskRel
>
> HaskRel employs a Data.Set of Data.HList.Record as a relation type, for
> which it
> defines "Relation" as a synonym. It supports base variables (files) of this
> type, and implements the functions of the relational algebra such that
> they can
> be expressed upon both constants or literal values, upon variables, and
> upon
> expressions on variables.
>
> Example
> -------
>
> The following is a minimal definition of a database with a single relation
> variable, "sp":
>
> module MiniDB where
>
> import Data.HList.CommonMain
> import Database.HaskRel.RDBMS
>
> sp :: Relvar '[Attr "sno" String,
>                Attr "pno" String,
>                Attr "qty" Integer]
> sp  = Relvar "SP.rv"
>
>
> "Attr" has been defined as a synonym for "Data.Tagged.Tagged", because
> that is
> employed to represent what are known as attributes in relational theory.
> Loading
> this in GHCi we can first create a relation constant, do some relational
> assignment, and print the results (pardon the long lines):
>
> *MiniDB> let s = ( relation' [ ( "S1", "Smith", 20, "London" ), ( "S2",
> "Jones", 10, "Paris" ), ( "S3", "Blake", 30, "Paris" ) ] :: Relation '[Attr
> "sno" String, Attr "sName" String, Attr "status" Integer, Attr "city"
> String] )
> *MiniDB> pt s
> ┌───────────────┬─────────────────┬───────────────────┬────────────────┐
> │ sno :: String │ sName :: String │ status :: Integer │ city :: String │
> ╞═══════════════╪═════════════════╪═══════════════════╪════════════════╡
> │ S1            │ Smith           │ 20                │ London         │
> │ S2            │ Jones           │ 10                │ Paris          │
> │ S3            │ Blake           │ 30                │ Paris          │
> └───────────────┴─────────────────┴───────────────────┴────────────────┘
> *MiniDB> sp `assign` ( relation' [ ("S1", "P1", 300), ("S1", "P3", 400),
> ("S1", "P5", 100), ("S2", "P1", 300), ("S3", "P2", 200) ] :: Relation
> '[Attr "sno" String, Attr "pno" String, Attr "qty" Integer] )
> Value assigned to ./SP.rv
> *MiniDB> pt sp
> ┌───────────────┬───────────────┬────────────────┐
> │ sno :: String │ pno :: String │ qty :: Integer │
> ╞═══════════════╪═══════════════╪════════════════╡
> │ S1            │ P1            │ 300            │
> │ S1            │ P3            │ 400            │
> │ S1            │ P5            │ 100            │
> │ S2            │ P1            │ 300            │
> │ S3            │ P2            │ 200            │
> └───────────────┴───────────────┴────────────────┘
>
>
> (Mind that correct display of the Unicode table drawing characters depends
> on
> using the right fixed-width font.)
>
> Fundamental operations of the relational algebra can of course be
> performed on
> them:
>
> *MiniDB> p $ s `naturalJoin` sp
> ┌─────┬───────┬────────┬────────┬─────┬─────┐
> │ sno │ sName │ status │ city   │ pno │ qty │
> ╞═════╪═══════╪════════╪════════╪═════╪═════╡
> │ S1  │ Smith │ 20     │ London │ P1  │ 300 │
> │ S1  │ Smith │ 20     │ London │ P3  │ 400 │
> │ S1  │ Smith │ 20     │ London │ P5  │ 100 │
> │ S2  │ Jones │ 10     │ Paris  │ P1  │ 300 │
> │ S3  │ Blake │ 30     │ Paris  │ P2  │ 200 │
> └─────┴───────┴────────┴────────┴─────┴─────┘
>
>
> A proper relational database management system (which, again, this isn't,
> for
> several other reasons) must support type inference for relational
> expressions
> (see The Third Manifesto, relational model prescription 18). Fortunately,
> that
> is of course no problem for GHC with the right extensions:
>
> *MiniDB> :t s
> s :: Relation
>        '[Attr "sno" String, Attr "sName" String, Attr "status" Integer,
>          Attr "city" String]
> *MiniDB> :t sp
> sp
>   :: Relvar
>        '[Attr "sno" String, Attr "pno" String, Attr "qty" Integer]
> *MiniDB> :t s `naturalJoin` sp
> s `naturalJoin` sp
>   :: IO
>        (containers-0.5.6.2:Data.Set.Base.Set
>           (RTuple
>              '[Tagged "sno" String, Tagged "sName" String,
>                Tagged "status" Integer, Tagged "city" String, Tagged "pno"
> [Char],
>                Tagged "qty" Integer]))
>
>
> DML is also supported, of course:
>
> *MiniDB> insert sp ( relation' [ ("S1", "P2", 200), ("S1", "P3", 400),
> ("S1", "P4", 200) ] :: Relation '[Attr "sno" String, Attr "pno" String,
> Attr "qty" Integer] )
> Inserted 2 of 3 tuples into ./SP.rv
>
>
> Concise expression of "update" require a set of language extensions (this
> in
> addition to DataKinds, which this module enables by default since it is
> quite
> ubiquitous in this endeavor):
>
> *MiniDB> :set -XQuasiQuotes -XKindSignatures -XViewPatterns
> *MiniDB> :{
> *MiniDB| update sp (\[pun|pno qty|] -> ( pno == "P2" || pno == "P3" || pno
> == "P4" ) && qty < 300 )
> *MiniDB|           (\[pun|qty|] -> case qty + 50 of qty -> [pun|qty|])
> *MiniDB| :}
> Updated 3 of 7 tuples in ./SP.rv
> *MiniDB> pt$ sp `restrict` \[pun|pno|] -> ( pno == "P2" || pno == "P3" ||
> pno == "P4" )
> ┌───────────────┬───────────────┬────────────────┐
> │ sno :: String │ pno :: String │ qty :: Integer │
> ╞═══════════════╪═══════════════╪════════════════╡
> │ S1            │ P2            │ 250            │
> │ S1            │ P3            │ 400            │
> │ S1            │ P4            │ 250            │
> │ S3            │ P2            │ 250            │
> └───────────────┴───────────────┴────────────────┘
>
>
> And of course delete-by-predicate:
>
> *MiniDB> count sp
> 7
> *MiniDB> deleteP sp (\[pun|pno|] -> pno == "P3")
> Deleted 1 tuples from SP.rv
> *MiniDB> count sp
> 6
>
>
> For an overview of the functions of the relational algebra and relational
> assignment defined by HaskRel see:
>
>
> http://hackage.haskell.org/package/HaskRel/docs/Database-HaskRel-Relational-Expression.html
>
> Summary
> -------
>
> This is a personal, spare-time project, the motivations for which have
> been to
> learn Haskell, and see how much of the relational model Haskell/GHC can
> accommodate, or how much like an RDBMS GHC can operate. Making this
> practically
> usable has not been part of the scope.
>
> Ascertaining that Haskell/GHC accommodates the relational algebra,
> relational
> base variables and operations thereupon in such a straight forward manner,
> was
> quite nice. It was particularly fun to see how this allowed examples of
> expressions in Tutorial D from Chris Date's "SQL and Relational Theory,
> 2nd. ed"
> to be expressed in Haskell in a manner quite verbatim to the originals (see
>
> https://github.com/thormick/HaskRel/blob/master/HaskRel/examples/SuppliersPartsExample.hs
> and chapters 6 and 7 of said book). It was also interesting to see trivial
> querying and DML operations on GHCi operate in a manner similar to what one
> would expect in a DBMS.
>
> Even if this isn't of practical use I still hope it is of some interest,
> or at
> least that it can enable Haskell as a demonstrator of some parts of the
> relational model for database management.
>
> Thanks,
> Thor Michael Støre
>
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell/attachments/20151231/0817aafb/attachment-0001.html>


More information about the Haskell mailing list