1
1
mirror of https://github.com/github/semantic.git synced 2024-12-22 14:21:31 +03:00

Add a function to decorate a term with its label.

This commit is contained in:
Rob Rix 2016-08-04 15:27:14 -04:00
parent 59ef5efd1e
commit bb6cbb753c
2 changed files with 5 additions and 1 deletions

View File

@ -110,6 +110,10 @@ featureVector d bag = sumVectors $ unitDVector . hash <$> bag
featureVectorDecorator :: (Prologue.Foldable f, Functor f) => (forall b. CofreeF f (Record a) b -> label) -> Int -> Int -> Int -> TermDecorator f a (Vector.Vector Double)
featureVectorDecorator getLabel p q d (a :< s) = Vector.replicate d 0
decorateTermWithLabel :: (Typeable label, Functor f) => (forall b. CofreeF f (Record fields) b -> label) -> Cofree f (Record fields) -> Cofree f (Record (label ': fields))
decorateTermWithLabel getLabel = cata $ \ c@(h :< t) ->
cofree ((getLabel c .: h) :< t)
-- | The magnitude of a Euclidean vector, i.e. its distance from the origin.
vmagnitude :: Vector.Vector Double -> Double

View File

@ -1,6 +1,6 @@
{-# LANGUAGE DataKinds, GADTs, KindSignatures, MultiParamTypeClasses, ScopedTypeVariables, TypeOperators #-}
module Data.Record
( Record(RNil)
( Record(..)
, (.:)
, HasField(..)
, maybeGetField