Commit a47efda1 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FEAT PUBLIC] Home canvas

parent 4a090915
module Gargantext.Components.Nodes.Home where module Gargantext.Components.Nodes.Home where
import Prelude import Data.Array (replicate)
import Data.Foldable (foldl)
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Effect (Effect) import Effect (Effect)
import Gargantext.Components.Data.Landing (BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.Lang (LandingLang(..))
import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Nodes.Home.Public (PublicData(..), publicLayout)
import Gargantext.License (license)
import Gargantext.Prelude (Unit, bind, map, pure, unit, void, ($), (<>))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Routing.Hash (setHash) import Routing.Hash (setHash)
import Gargantext.License (license)
import Gargantext.Components.Lang.Landing.EnUS as En
import Gargantext.Components.Lang.Landing.FrFR as Fr
import Gargantext.Components.Data.Landing
(BlockText(..), BlockTexts(..), Button(..), LandingData(..))
import Gargantext.Components.Lang (LandingLang(..))
type Props = () type Props = ()
...@@ -48,15 +50,27 @@ homeLayout lang = R.createElement homeLayoutCpt {landingData} [] ...@@ -48,15 +50,27 @@ homeLayout lang = R.createElement homeLayoutCpt {landingData} []
where landingData = langLandingData lang where landingData = langLandingData lang
homeLayoutCpt :: R.Component ( landingData :: LandingData ) homeLayoutCpt :: R.Component ( landingData :: LandingData )
homeLayoutCpt = R.staticComponent "LayoutLanding" cpt homeLayoutCpt = R.hooksComponent "LayoutLanding" cpt
where where
cpt {landingData} _ = cpt {landingData} _ = do
H.span {} pds <- R.useState' ( replicate 6 (PublicData { title: "Title"
[ H.div { className: "container1" } [ jumboTitle landingData false ] , abstract : foldl (<>) "" $ replicate 100 "abstract "
, H.div { className: "container1" } [] -- TODO put research form , img: "images/Gargantextuel-212x300.jpg"
, H.div { className: "container1" } [ blocksRandomText' landingData ] , url : "https://.."
, license , date: "YY/MM/DD"
] , database: "database"
, author : "Author"
}
)
)
pure $ H.span {}
[ H.div { className: "container1" } [ jumboTitle landingData false ]
, H.div { className: "container1" } [] -- TODO put research form
, H.div { className: "container1" } [ blocksRandomText' landingData ]
, H.div { className: "container1" } [ publicLayout {publicDatas:pds} ]
, license
]
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -89,6 +103,8 @@ docButton (Button b) = ...@@ -89,6 +103,8 @@ docButton (Button b) =
, H.text b.text , H.text b.text
] ]
-- | TODO
-- <img src='logo.png' onmouseover="this.src='gargantextuel.png';" onmouseout="this.src='logo.png';" />
jumboTitle :: LandingData -> Boolean -> R.Element jumboTitle :: LandingData -> Boolean -> R.Element
jumboTitle (LandingData hd) b = jumboTitle (LandingData hd) b =
H.div {className: jumbo} H.div {className: jumbo}
......
module Gargantext.Components.Nodes.Home.Public where
import Data.String (take)
import Gargantext.Prelude
import Data.Tuple.Nested ((/\))
import Data.Newtype (class Newtype)
import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Sessions (Session(..))
type PublicProps = (publicDatas :: R.State (Array PublicData)
-- , session :: Session
)
newtype PublicData = PublicData
{ title :: String
, abstract :: String
, img :: String
, url :: String
, date :: String
, database :: String
, author :: String
}
publicLayout :: Record PublicProps -> R.Element
publicLayout props = R.createElement publicLayoutCpt props []
publicLayoutCpt :: R.Component PublicProps
publicLayoutCpt = R.staticComponent "[G.C.N.H.Public.publicLayout" cpt
where
cpt {publicDatas} _ =
H.span {}
[ H.div { className: "container1" } [ H.h2 {} [H.text "Public Maps"]]
-- | TODO browse maps
-- | TODO random maps
, album pds
]
where
(pds /\ _setPublicData) = publicDatas
album :: Array PublicData -> R.Element
album pd = H.div {className: "album py-5 bg-light"}
[ H.div { className: "container" }
[ H.div { className : "row" }
(map (\tab -> H.div {className : "col-md-6 content"} [tableau tab]) pd )
]
]
tableau :: PublicData -> R.Element
tableau (PublicData {title, abstract, img, url, date, database, author}) =
H.div {className: "card mb-6 box-shadow"}
[ H.a { target: "_blank", href: url } [ H.div { className:"center"}
[H.img { src: img
, width: "50%"
}
]
]
, H.div { className : "card-body"}
[ H.h3 {} [H.text title]
, H.p { className: "card-text"} [H.text $ (take 252 abstract) <> "..."]
, H.div { className: "center justify-content-between align-items-center"}
[ H.div { className: "btn-group" }
[ H.button { className : "btn btn-default flex-between"
, href : url
, role : "button"
} [ H.text "View the map" ]
{- TODO
, H.button { className : "btn btn-default flex-start"
, href : url
, role : "button"
} [ H.text "More like this" ]
-}
]
, H.div { className : "small text-muted flex-end" } [ H.text $ "Made by " <> author
<> " on " <> date
<> " with " <> database
]
]
]
]
...@@ -50,10 +50,12 @@ randomChars word = case (length (toCharArray word)) >= 5 of ...@@ -50,10 +50,12 @@ randomChars word = case (length (toCharArray word)) >= 5 of
------------------------------------------------------------------- -------------------------------------------------------------------
words :: String -> Array String words :: String -> Array String
words sentence = filter ((/=) "") $ split (Pattern " ") sentence words sentence = filter ((/=) "")
$ split (Pattern " ") sentence
sentences :: String -> Array String sentences :: String -> Array String
sentences paragraph = filter ((/=) "") $ split (Pattern ".") paragraph sentences paragraph = filter ((/=) "")
$ split (Pattern ".") paragraph
------------------------------------------------------------------- -------------------------------------------------------------------
...@@ -63,7 +65,8 @@ data RandomWheel a = RandomWheel { before :: Array a ...@@ -63,7 +65,8 @@ data RandomWheel a = RandomWheel { before :: Array a
} }
randomPart :: forall b. Array b -> Effect (Array b) randomPart :: forall b. Array b -> Effect (Array b)
randomPart array = randomArrayPoly middle >>= \(middle') -> pure ( start <> middle' <> end) randomPart array = randomArrayPoly middle
>>= \(middle') -> pure ( start <> middle' <> end)
where where
start = take 2 array start = take 2 array
middle = dropEnd 2 $ drop 2 array middle = dropEnd 2 $ drop 2 array
...@@ -93,7 +96,7 @@ randomArray array = unsafePartial $ do ...@@ -93,7 +96,7 @@ randomArray array = unsafePartial $ do
case maybeDuring of case maybeDuring of
Nothing -> Nothing ->
crash "[ERROR] It should never happen." crash "[G.C.N.H.R.RandomText ERROR] It should never happen."
Just during -> Just during ->
pure $ RandomWheel { before : remove n array pure $ RandomWheel { before : remove n array
, during : during , during : during
......
...@@ -24,7 +24,8 @@ newtype Backend = Backend ...@@ -24,7 +24,8 @@ newtype Backend = Backend
{ name :: String { name :: String
, baseUrl :: String , baseUrl :: String
, prePath :: String , prePath :: String
, version :: ApiVersion } , version :: ApiVersion
}
backend :: ApiVersion -> String -> String -> String -> Backend backend :: ApiVersion -> String -> String -> String -> Backend
backend version prePath baseUrl name = Backend { name, version, prePath, baseUrl } backend version prePath baseUrl name = Backend { name, version, prePath, baseUrl }
......
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