Skip to content
Snippets Groups Projects
Commit 7e90dfce authored by Alice Brenon's avatar Alice Brenon
Browse files

Adapt compute-profile to latest changes in Conllu.Tree*

parent ea0e05e5
No related branches found
No related tags found
No related merge requests found
...@@ -2,11 +2,12 @@ ...@@ -2,11 +2,12 @@
{-# LANGUAGE DeriveGeneric, ExplicitNamespaces #-} {-# LANGUAGE DeriveGeneric, ExplicitNamespaces #-}
import Conllu.Tree import Conllu.Tree
( Feat(..), IndexedDocument(..), IndexedSentence(..), IndexedWord(..) ( Feat(..), IndexedDocument(..), IndexedSentence(..), IndexedToken(..)
, positions ) , positions )
import Control.Applicative ((<**>)) import Control.Applicative ((<**>))
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Control.Monad.Reader (ReaderT, asks, runReaderT) import Control.Monad.Reader (ReaderT, asks, runReaderT)
import Conllu.Tree.Count (Count(..))
import Data.Csv (DefaultOrdered(..), ToNamedRecord(..)) import Data.Csv (DefaultOrdered(..), ToNamedRecord(..))
import Data.ByteString as ByteString (readFile) import Data.ByteString as ByteString (readFile)
import Data.List (sort) import Data.List (sort)
...@@ -63,11 +64,13 @@ profile articleRecord = do ...@@ -63,11 +64,13 @@ profile articleRecord = do
analyse = pure . fmap (glue articleRecord) . findOccurrences analyse = pure . fmap (glue articleRecord) . findOccurrences
findOccurrences :: IndexedDocument -> [Occurrence] findOccurrences :: IndexedDocument -> [Occurrence]
findOccurrences (IndexedDocument {_total, _sentences}) = findOccurrences (IndexedDocument {_total = Count {tokens}, _sentences}) =
groupOccurrences [] (_sentences >>= imperativeVerb) groupOccurrences [] (_sentences >>= imperativeVerb)
where where
occurrence (position, size) =
Occurrence {event = "Imperative", position, size, totalSize = tokens}
groupOccurrences :: [(Int, Int)] -> [Int] -> [Occurrence] groupOccurrences :: [(Int, Int)] -> [Int] -> [Occurrence]
groupOccurrences stack [] = uncurry (Occurrence _total) <$> reverse stack groupOccurrences stack [] = occurrence <$> reverse stack
groupOccurrences [] (p:ps) = groupOccurrences [(p, 1)] ps groupOccurrences [] (p:ps) = groupOccurrences [(p, 1)] ps
groupOccurrences (tmp@(first, tmpLength):stack) (p:ps) groupOccurrences (tmp@(first, tmpLength):stack) (p:ps)
| p == first + tmpLength = | p == first + tmpLength =
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment