discokitty: DisCoCat implementation.

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

An educational implementation of the DisCoCat framework.


[Skip to Readme]

Properties

Versions 0.1.0, 0.1.0
Change log None available
Dependencies base (>=4.7 && <5), containers (>=0.5.7.1) [details]
License GPL-3.0-only
Author Mario Román (mroman42)
Maintainer mromang08+github@gmail.com
Category Language
Home page https://github.com/mroman42/discokitty
Bug tracker https://github.com/mroman42/discokitty/issues
Source repo head: git clone git://github.com/mroman42/discokitty.git
Uploaded by mroman42 at 2019-05-13T13:24:09Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for discokitty-0.1.0

[back to package description]

discokitty

Version

An educational implementation of the DisCoCat framework as described in "Mathematical Foundations for a Compositional Distributional Model of Meaning" (link) by Coecke, Sadrzadeh and Clark.

Sunglasses Kitty by Rikki Lorie, licensed under Creative Commons

Usage example

Please note that this library is work in progress and it is possible that substantial changes will be made. In the following example we work in the category of relations declaring the meaning and grammar type of some words and then we evaluate an example sentence.

module Discokitty.Examples.AliceAndBob where

import           Discokitty
import           Discokitty.Models.Diagrams
import           Discokitty.Models.Rel

-- We first declare an universe with all the possible basis words,
-- both nouns and sentences.  The rest of the types are parameterized
-- by this universe.
data Universe = Alice | Bob | IsTrue | IsFalse deriving (Eq, Ord, Show)

-- We choose to use the category of relations for this example, and we
-- declare a term to be a word in the category of relations for our
-- given universe.
type Term = Words (Rel Universe)

-- We give meaning to some terms.  Relations are described as subsets using
-- "relation", and the Lambek grammatical type must be written at the end.
alice :: Term
alice = Words
  { meaning = relation [ [ Alice ] ]
  , grammar = [N]
  , text = "Alice"
  }

bob :: Term
bob = Words
  { meaning = relation [ [ Bob ] ]
  , grammar = [N]
  , text = "Bob"
  }

loves :: Term
loves = Words
  { meaning = relation [ [ Alice , IsTrue , Bob ] ]
  , grammar = [ L N , S , R N ]
  , text = "loves"
  }


-- In our example sentence, we evaluate "Alice loves Bob".
-- This produces the following output:
--   > [[IsTrue]] of grammar type [S]
example :: [Term]
example = sentence [alice , loves , bob] @@@ [S]


-- We can also generate Tikz diagrams.
exampleDiagram :: String
exampleDiagram = tikzDiagrams [alice , loves , bob]

The generated tikz diagram looks as follows.