Commit 5d74f5b4 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[WIP/RESEARCH] Niveau Texte.

parent e21d93ed
......@@ -13,10 +13,14 @@ Text gathers terms in unit of contexts.
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Gargantext.Text
where
import Data.Functor
import Data.Traversable (Traversable)
import Data.Text (Text, split)
import qualified Data.Text as DT
......@@ -25,12 +29,74 @@ import NLP.FullStop (segment)
import Gargantext.Core
import Gargantext.Prelude hiding (filter)
-----------------------------------------------------------------
-- | Why not use data ?
data Niveau = NiveauTexte Texte
| NiveauParagraphe Paragraphe
| NiveauPhrase Phrase
| NiveauMultiTerme MultiTerme
| NiveauMot Mot
| NiveauLettre Lettre
deriving (Show)
-- | Why use newtype ?
newtype Texte = Texte Text
newtype Paragraphe = Paragraphe Text
newtype Phrase = Phrase Text
newtype MultiTerme = MultiTerme Text
newtype Mot = Mot Text
newtype Lettre = Lettre Text
-- | Type syn seems obvious
type Titre = Phrase
-----------------------------------------------------------------
instance Show Texte where
show (Texte t) = show t
instance Show Paragraphe where
show (Paragraphe p) = show p
instance Show Phrase where
show (Phrase p) = show p
instance Show MultiTerme where
show (MultiTerme mt) = show mt
instance Show Mot where
show (Mot t) = show t
type Config = Lang -> Context
type Context = Text -> [Text]
data Viz = Graph | Phylo | Chart
instance Show Lettre where
show (Lettre l) = show l
-----------------------------------------------------------------
class Collage sup inf where
dec :: sup -> [inf]
inc :: [inf] -> sup
instance Collage Texte Paragraphe where
dec (Texte t) = map Paragraphe $ DT.splitOn "\n" t
inc = Texte . DT.intercalate "\n" . map (\(Paragraphe t) -> t)
instance Collage Paragraphe Phrase where
dec (Paragraphe t) = map Phrase $ sentences t
inc = Paragraphe . DT.unwords . map (\(Phrase p) -> p)
instance Collage Phrase MultiTerme where
dec (Phrase t) = map MultiTerme $ DT.words t
inc = Phrase . DT.unwords . map (\(MultiTerme p) -> p)
instance Collage MultiTerme Mot where
dec (MultiTerme mt) = map Mot $ DT.words mt
inc = MultiTerme . DT.intercalate " " . map (\(Mot m) -> m)
-- | We could use Type Classes but we lose the Sum Type classification
toMultiTerme :: Niveau -> [MultiTerme]
toMultiTerme (NiveauTexte (Texte t)) = undefined
toMultiTerme (NiveauPhrase p) = dec p
toMultiTerme (NiveauMultiTerme mt) = [mt]
toMultiTerme (NiveauMot m) = undefined
-------------------------------------------------------------------
-- Contexts of text
sentences :: Text -> [Text]
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment