Portability | non-portable (H98 + implicit parameters) |
---|---|
Stability | experimental |
Maintainer | hdaume@isi.edu |
Safe Haskell | None |
NLP.WordNet
Contents
- The basic type system
- The wrapper type for wordnet functions.
- The basic Word type (just a
String
). - The part of speech type.
- The type, and functions dealing with overview searches.
- The type, and functions dealing with the word net environment.
- The type to control which sense a search is looking at.
- The type, and functions dealing with search results.
- A sum type of the different relations which can hold between words.
- A simple key into the database.
- Top level execution functions
- Functions to manually initialize the WordNet system; these are not
- The basic database access functions.
- The agglomeration functions
- Computing lowest-common ancestor functions; the implementation
Description
This is the top level module to the Haskell WordNet interface.
This module is maintained at: http://www.isi.edu/~hdaume/HWordNet/.
This is the only module in the WordNet package you need to import. The others provide utility functions and primitives that this module is based on.
More information about WordNet is available at: http://http://www.cogsci.princeton.edu/~wn/.
- type WN a = [wne :: WordNetEnv] => a
- type Word = String
- data POS
- data Overview
- numNounSenses :: Overview -> Int
- numVerbSenses :: Overview -> Int
- numAdjSenses :: Overview -> Int
- numAdvSenses :: Overview -> Int
- taggedCountNounSenses :: Overview -> Int
- taggedCountVerbSenses :: Overview -> Int
- taggedCountAdjSenses :: Overview -> Int
- taggedCountAdvSenses :: Overview -> Int
- data WordNetEnv
- getReleaseVersion :: WN (Maybe String)
- getDataDirectory :: WN FilePath
- data SenseType
- = AllSenses
- | SenseNumber Int
- data SearchResult
- srOverview :: SearchResult -> Maybe Overview
- srSenseNum :: SearchResult -> Maybe SenseType
- srPOS :: SearchResult -> POS
- srDefinition :: SearchResult -> String
- srSenses :: SearchResult -> [SenseType]
- srWords :: SearchResult -> SenseType -> [Word]
- srForms :: SearchResult -> [Form]
- srFormKeys :: SearchResult -> Form -> [Key]
- srToKey :: SearchResult -> Key
- data Form
- = Antonym
- | Hypernym
- | Hyponym
- | Entailment
- | Similar
- | IsMember
- | IsStuff
- | IsPart
- | HasMember
- | HasStuff
- | HasPart
- | Meronym
- | Holonym
- | CauseTo
- | PPL
- | SeeAlso
- | Attribute
- | VerbGroup
- | Derivation
- | Classification
- | Class
- | Nominalization
- | Syns
- | Freq
- | Frames
- | Coords
- | Relatives
- | HMeronym
- | HHolonym
- | WNGrep
- | OverviewForm
- | Unknown
- data Key
- runWordNet :: WN a -> IO a
- runWordNetQuiet :: WN a -> IO a
- runWordNetWithOptions :: Maybe FilePath -> Maybe (String -> SomeException -> IO ()) -> WN a -> IO a
- initializeWordNet :: IO WordNetEnv
- initializeWordNetWithOptions :: Maybe FilePath -> Maybe (String -> SomeException -> IO ()) -> IO WordNetEnv
- closeWordNet :: WordNetEnv -> IO ()
- runs :: WordNetEnv -> WN a -> a
- getOverview :: WN (Word -> Overview)
- searchByOverview :: WN (Overview -> POS -> SenseType -> [SearchResult])
- search :: WN (Word -> POS -> SenseType -> [SearchResult])
- lookupKey :: WN (Key -> SearchResult)
- relatedBy :: WN (Form -> SearchResult -> [SearchResult])
- closure :: (a -> [a]) -> a -> Tree a
- closureOn :: WN (Form -> SearchResult -> Tree SearchResult)
- meet :: Bag b (Tree SearchResult) => WN (b (Tree SearchResult) -> SearchResult -> SearchResult -> Maybe SearchResult)
- meetPaths :: Bag b (Tree SearchResult) => WN (b (Tree SearchResult) -> SearchResult -> SearchResult -> Maybe ([SearchResult], SearchResult, [SearchResult]))
- meetSearchPaths :: Bag b (Tree SearchResult) => b (Tree SearchResult) -> Tree SearchResult -> Tree SearchResult -> Maybe ([SearchResult], SearchResult, [SearchResult])
- class Bag b a where
- emptyBag :: b a
- addToBag :: b a -> a -> b a
- addListToBag :: b a -> [a] -> b a
- isEmptyBag :: b a -> Bool
- splitBag :: b a -> (a, b a)
- emptyQueue :: Queue a
- emptyStack :: [a]
The basic type system
The wrapper type for wordnet functions.
type WN a = [wne :: WordNetEnv] => aSource
In actuality this type is:
type WN a = (?wne :: WordNetEnv) => a
but Haddock cannot parse this at this time. type WN a = a
The basic Word type (just a String
).
The part of speech type.
The type, and functions dealing with overview searches.
The Overview
type is the return type which gives you an
overview of a word, for all sense and for all parts of speech.
numNounSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many noun senses the searched-for word has.
numVerbSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many verb senses the searched-for word has.
numAdjSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many adjective senses the searched-for word has.
numAdvSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many adverb senses the searched-for word has.
taggedCountNounSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many times this word was tagged as a noun.
taggedCountVerbSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many times this word was tagged as a verb.
taggedCountAdjSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many times this word was tagged as an adjective.
taggedCountAdvSenses :: Overview -> IntSource
Given an Overview
, this will tell you how many times this word was tagged as an adverb.
The type, and functions dealing with the word net environment.
data WordNetEnv Source
getReleaseVersion :: WN (Maybe String)Source
This will give you the current release of the WordNet databases we are using (if we know).
getDataDirectory :: WN FilePathSource
This will give you the directory from which the databases are being read.
The type to control which sense a search is looking at.
A SenseType
is a way of controlling search. Either you specify
a certain sense (using SenseNumber n
, or, since SenseType
is an
instance of Num
, you can juse use n
) or by searching using all
senses, through AllSenses
. The Num
instance performs standard
arithmetic on SenseNumber
s, and fromInteger
yields a SenseNumber
(always),
but any arithmetic involving AllSenses
returns AllSenses
.
Constructors
AllSenses | |
SenseNumber Int |
The type, and functions dealing with search results.
data SearchResult Source
The basic type which holds search results. Its Show
instance simply
shows the string corresponding to the associated WordNet synset.
Instances
srOverview :: SearchResult -> Maybe OverviewSource
This provides (maybe) the associated overview for a SearchResult.
The Overview
is only available if this SearchResult
was
derived from a real search, rather than lookupKey
.
srSenseNum :: SearchResult -> Maybe SenseTypeSource
This provides (maybe) the associated sense number for a SearchResult.
The SenseType
is only available if this SearchResult
was
derived from a real search, rather than lookupKey
.
srPOS :: SearchResult -> POSSource
This gives the part of speech of a SearchResult
srDefinition :: SearchResult -> StringSource
This gives the definition of the sense of a word in a SearchResult
.
srSenses :: SearchResult -> [SenseType]Source
This gives a list of senses the word has.
srWords :: SearchResult -> SenseType -> [Word]Source
This gives the actual words used to describe the Synset of a search result.
srForms :: SearchResult -> [Form]Source
This gives all the Form
s a word has (i.e., what sort of relations hold between
it and other words.
srFormKeys :: SearchResult -> Form -> [Key]Source
This provides a Key
(which can be searched for using lookupKey
) for
a SearchResult
under a given form. For instance, it can be used to
get all Hypernym
s of a given word.
srToKey :: SearchResult -> KeySource
This converts a SearchResult
into a Key
.
A sum type of the different relations which can hold between words.
The different types of relations which can hold between WordNet Synsets.
A simple key into the database.
A Key
is a simple pointer into the database, which can be
followed using lookupKey
.
Top level execution functions
runWordNet :: WN a -> IO aSource
Takes a WordNet command, initializes the environment
and returns the results in the IO
monad. WordNet
warnings are printed to stderr.
runWordNetQuiet :: WN a -> IO aSource
Takes a WordNet command, initializes the environment
and returns the results in the IO
monad. WordNet
warnings are ignored.
runWordNetWithOptions :: Maybe FilePath -> Maybe (String -> SomeException -> IO ()) -> WN a -> IO aSource
Takes a FilePath to the directory holding WordNet and
a function to do with warnings and a WordNet command, initializes
the environment and returns the results in the IO
monad.
Functions to manually initialize the WordNet system; these are not
initializeWordNet :: IO WordNetEnvSource
Gives you a WordNetEnv
which can be passed to runs
or used
as the implicit parameter to the other WordNet functions.
initializeWordNetWithOptions :: Maybe FilePath -> Maybe (String -> SomeException -> IO ()) -> IO WordNetEnvSource
Takes a FilePath to the directory holding WordNet and
a function to do with warnings, initializes
the environment and returns a WordNetEnv
as in initializeWordNet
.
closeWordNet :: WordNetEnv -> IO ()Source
Closes all the handles associated with the WordNetEnv
. Since
the functions provided in the NLP.WordNet.WordNet module
are lazy, you shouldn't do this until you're really done.
Or perhaps not at all (GC will eventually kick in).
runs :: WordNetEnv -> WN a -> aSource
This simply takes a WordNetEnv
and provides it as the
implicit parameter to the WordNet command.
The basic database access functions.
getOverview :: WN (Word -> Overview)Source
This takes a word and returns an Overview
of all its senses
for all parts of speech.
searchByOverview :: WN (Overview -> POS -> SenseType -> [SearchResult])Source
This takes an Overview
(see getOverview
), a POS
and a SenseType
and returns
a list of search results. If SenseType
is AllSenses
, there will be one
SearchResult
in the results for each valid sense. If SenseType
is
a single sense number, there will be at most one element in the result list.
search :: WN (Word -> POS -> SenseType -> [SearchResult])Source
This takes a Word
, a POS
and a SenseType
and returns
the equivalent of first running getOverview
and then searchByOverview
.
lookupKey :: WN (Key -> SearchResult)Source
This takes a Key
(see srToKey
and srFormKeys
) and looks it
up in the databse.
The agglomeration functions
relatedBy :: WN (Form -> SearchResult -> [SearchResult])Source
This takes a Form
and a SearchResult
and returns all
SearchResult
related to the given one by the given Form
.
For example:
relatedBy Antonym (head (search "happy" Adj 1)) [<unhappy>] relatedBy Hypernym (head (search "dog" Noun 1)) [<canine canid>]
closure :: (a -> [a]) -> a -> Tree aSource
This is a utility function to build lazy trees from a function and a root.
closureOn :: WN (Form -> SearchResult -> Tree SearchResult)Source
This enables Form
-based trees to be built.
For example:
take 5 $ flatten $ closureOn Antonym (head (search "happy" Adj AllSenses))) [<happy>,<unhappy>,<happy>,<unhappy>,<happy>]
closureOn Hypernym (head (search "dog" Noun 1))) - <dog domestic_dog Canis_familiaris> --- <canine canid> --- <carnivore>\-- > --- <placental placental_mammal eutherian eutherian_mammal> --- <mammal>\-- > --- <vertebrate craniate> --- <chordate> --- <animal animate_being beast\-- > brute creature fauna> --- <organism being> --- <living_thing animate_thing>\-- > --- <object physical_object> --- <entity>
Computing lowest-common ancestor functions; the implementation
meet :: Bag b (Tree SearchResult) => WN (b (Tree SearchResult) -> SearchResult -> SearchResult -> Maybe SearchResult)Source
This function takes an empty bag (in particular, this is to specify what type of search to perform), and the results of two search. It returns (maybe) the lowest point at which the two terms meet in the WordNet hierarchy.
For example:
meet emptyQueue (head $ search "cat" Noun 1) (head $ search "dog" Noun 1) Just <carnivore>
meet emptyQueue (head $ search "run" Verb 1) (head $ search "walk" Verb 1) Just <travel go move locomote>
meetPaths :: Bag b (Tree SearchResult) => WN (b (Tree SearchResult) -> SearchResult -> SearchResult -> Maybe ([SearchResult], SearchResult, [SearchResult]))Source
This function takes an empty bag (see meet
), and the results of two searches.
It returns (maybe) the lowest point at which the two terms
meet in the WordNet hierarchy, as well as the paths leading from each
term to this common term.
For example:
meetPaths emptyQueue (head $ search "cat" Noun 1) (head $ search "dog" Noun 1) Just ([<cat true_cat>,<feline felid>],<carnivore>,[<canine canid>,<dog domestic_dog Canis_familiaris>])
meetPaths emptyQueue (head $ search "run" Verb 1) (head $ search "walk" Verb 1) Just ([<run>,<travel_rapidly speed hurry zip>],<travel go move locomote>,[<walk>])
This is marginally less efficient than just using meet
, since it uses
linear-time lookup for the visited sets, whereas meet
uses log-time
lookup.
meetSearchPaths :: Bag b (Tree SearchResult) => b (Tree SearchResult) -> Tree SearchResult -> Tree SearchResult -> Maybe ([SearchResult], SearchResult, [SearchResult])Source
A simple bag class for our meet
implementation.
Methods
addToBag :: b a -> a -> b aSource
addListToBag :: b a -> [a] -> b aSource
isEmptyBag :: b a -> BoolSource
Instances
Bag [] a |
emptyQueue :: Queue aSource
An empty queue.
emptyStack :: [a]Source
An empty stack.