Routes.purs 6.54 KB
Newer Older
1 2 3
module Gargantext.Routes where

import Prelude
4

5 6
import Data.Maybe (Maybe(..))

7
import Gargantext.Types (ChartOpts, ChartType, CorpusMetricOpts, CTabNgramType, Id, Limit,
8
                         ListId, DocId, ContactId, NgramsGetOpts, NgramsGetTableAllOpts, NodeType,
9
                         Offset, OrderBy, SearchOpts, SessionId, TabSubType, TabType, TermList)
10
import Gargantext.Types as GT
11 12

data AppRoute
13
  = Annuaire       SessionId Int
14
  | ContactPage    SessionId Int Int
15
  | Corpus         SessionId Int
16 17 18
  | CorpusDocument SessionId Int Int Int
  | Dashboard      SessionId Int
  | Document       SessionId Int Int
19 20 21 22
  | Folder         SessionId Int
  | FolderPrivate  SessionId Int
  | FolderPublic   SessionId Int
  | FolderShared   SessionId Int
23 24 25
  | Home
  | Lists          SessionId Int
  | Login
26
  | PGraphExplorer  SessionId Int
27
  | RouteFile       SessionId Int
28
  | RouteFrameCalc  SessionId Int
29
  | RouteFrameCode  SessionId Int
30
  | RouteFrameWrite SessionId Int
31 32 33
  | Team            SessionId Int
  | Texts           SessionId Int
  | UserPage        SessionId Int
34

35

36 37
derive instance eqAppRoute :: Eq AppRoute

38 39 40 41
data SessionRoute
  = Tab TabType (Maybe Id)
  | Children NodeType Offset Limit (Maybe OrderBy) (Maybe Id)
  | GetNgrams NgramsGetOpts (Maybe Id)
42
  | GetNgramsTableAll NgramsGetTableAllOpts (Maybe Id)
43
  | GetNgramsTableVersion { listId :: ListId, tabType :: TabType } (Maybe Id)
Alexandre Delanoë's avatar
Alexandre Delanoë committed
44
  | PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id)
45
  | PostNgramsChartsAsync (Maybe Id)
Alexandre Delanoë's avatar
Alexandre Delanoë committed
46
  -- ^ This name is not good. In particular this URL is used both in PUT and POST.
47 48 49
  | RecomputeNgrams   (TabSubType CTabNgramType) Id ListId
  | RecomputeListChart ChartType  CTabNgramType  Id ListId
  | NodeAPI       NodeType (Maybe Id) String
50
  | TreeFirstLevel (Maybe Id) String
51 52
  | GraphAPI      Id String
  | ListsRoute    ListId
53
  | ListDocument (Maybe ListId) (Maybe DocId)
54
  | Search        SearchOpts (Maybe Id)
55
  | CorpusMetrics CorpusMetricOpts  (Maybe Id)
56
  | CorpusMetricsHash { listId :: ListId, tabType :: TabType }  (Maybe Id)
57
  | Chart ChartOpts (Maybe Id)
58
  | ChartHash { chartType :: ChartType, listId :: Maybe ListId, tabType :: TabType } (Maybe Id)
59
  -- | AnnuaireContact AnnuaireId DocId
60 61

instance showAppRoute :: Show AppRoute where
62 63
  show Home                     = "Home"
  show Login                    = "Login"
64 65 66 67 68 69 70
  show (Folder        s i)      = "Folder"         <> show i <> " (" <> show s <> ")"
  show (FolderPrivate s i)      = "FolderPrivate"  <> show i <> " (" <> show s <> ")"
  show (FolderPublic  s i)      = "FolderPublic"   <> show i <> " (" <> show s <> ")"
  show (FolderShared  s i)      = "FolderShared"   <> show i <> " (" <> show s <> ")"
  show (Team          s i)      = "Team"           <> show i <> " (" <> show s <> ")"
  show (Corpus        s i)      = "Corpus"         <> show i <> " (" <> show s <> ")"
  show (Document    _ s i)      = "Document"       <> show i <> " (" <> show s <> ")"
71
  show (CorpusDocument s _ _ i) = "CorpusDocument" <> show i <> " (" <> show s <> ")"
72 73
  show (PGraphExplorer s i)     = "graphExplorer"  <> show i <> " (" <> show s <> ")"
  show (Dashboard      s i)     = "Dashboard"      <> show i <> " (" <> show s <> ")"
74 75 76 77 78
  show (Texts          s i)     = "texts"          <> show i <> " (" <> show s <> ")"
  show (Lists          s i)     = "lists"          <> show i <> " (" <> show s <> ")"
  show (Annuaire       s i)     = "Annuaire"       <> show i <> " (" <> show s <> ")"
  show (UserPage       s i)     = "User"           <> show i <> " (" <> show s <> ")"
  show (ContactPage  s a i)     = "Contact"        <> show a <> "::" <> show i <> " (" <> show s <> ")"
79 80
  show (RouteFrameWrite s i)    = "write"          <> show i <> " (" <> show s <> ")"
  show (RouteFrameCalc  s i)    = "calc"           <> show i <> " (" <> show s <> ")"
81
  show (RouteFrameCode  s i)    = "code"           <> show i <> " (" <> show s <> ")"
82
  show (RouteFile       s i)    = "file"           <> show i <> " (" <> show s <> ")"
83

84 85

appPath :: AppRoute -> String
86 87
appPath Home                 = ""
appPath Login                = "login"
88 89 90 91 92
appPath (Folder s i)         = "folder/"        <> show s <> "/" <> show i
appPath (FolderPrivate s i)  = "folderPrivate/" <> show s <> "/" <> show i
appPath (FolderPublic s i)   = "folderPublic/"  <> show s <> "/" <> show i
appPath (FolderShared s i)   = "folderShared/"  <> show s <> "/" <> show i
appPath (Team s i)           = "team/"          <> show s <> "/" <> show i
93
appPath (CorpusDocument s c l i) = "corpus/" <> show s <> "/" <> show c <> "/list/" <> show l <> "/document/" <> show i
94 95 96 97 98 99 100 101
appPath (Corpus s i)         = "corpus/"     <> show s <> "/" <> show i
appPath (Document s l i)     = "list/"       <> show s <> "/" <> show l <> "/document/" <> show i
appPath (Dashboard s i)      = "dashboard/"  <> show s <> "/" <> show i
appPath (PGraphExplorer s i) = "graph/"      <> show s <> "/" <> show i
appPath (Texts s i)          = "texts/"      <> show s <> "/" <> show i
appPath (Lists s i)          = "lists/"      <> show s <> "/" <> show i
appPath (Annuaire s i)       = "annuaire/"   <> show s <> "/" <> show i
appPath (UserPage s i)       = "user/"       <> show s <> "/" <> show i
102
appPath (ContactPage s a i)  = "annuaire/"   <> show s <> "/" <> show a <> "/contact/" <> show i
103 104
appPath (RouteFrameWrite s i) = "write/"     <> show s <> "/" <> show i
appPath (RouteFrameCalc s i)  = "calc/"      <> show s <> "/" <> show i
105
appPath (RouteFrameCode s i)  = "code/"      <> show s <> "/" <> show i
106
appPath (RouteFile s i)       = "file/"      <> show s <> "/" <> show i
107

108
nodeTypeAppRoute :: NodeType -> SessionId -> Int -> Maybe AppRoute
Karen Konou's avatar
Karen Konou committed
109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125
nodeTypeAppRoute GT.Annuaire s i       = Just $ Annuaire s i
nodeTypeAppRoute GT.Corpus s i         = Just $ Corpus s i
nodeTypeAppRoute GT.Dashboard s i      = Just $ Dashboard s i
nodeTypeAppRoute GT.Folder s i         = Just $ Folder s i
nodeTypeAppRoute GT.FolderPrivate s i  = Just $ FolderPrivate s i
nodeTypeAppRoute GT.FolderPublic s i   = Just $ FolderPublic s i
nodeTypeAppRoute GT.FolderShared s i   = Just $ FolderShared s i
nodeTypeAppRoute GT.Graph s i          = Just $ PGraphExplorer s i
nodeTypeAppRoute GT.NodeContact s i    = Just $ Annuaire s i
nodeTypeAppRoute GT.NodeFile s i       = Just $ RouteFile s i
nodeTypeAppRoute GT.NodeList s i       = Just $ Lists s i
nodeTypeAppRoute GT.NodeUser s i       = Just $ UserPage s i
nodeTypeAppRoute GT.Team s i           = Just $ Team s i
nodeTypeAppRoute GT.Texts s i          = Just $ Texts s i
nodeTypeAppRoute GT.NodeFrameWrite s i = Just $ RouteFrameWrite s i
nodeTypeAppRoute GT.NodeFrameCalc s i  = Just $ RouteFrameCalc s i
nodeTypeAppRoute _ _ _                 = Nothing