Skip to content

Commit

Permalink
Add some data to the document page.
Browse files Browse the repository at this point in the history
  • Loading branch information
noteed committed Sep 20, 2023
1 parent 51d4c0d commit 8ee4bf8
Showing 1 changed file with 55 additions and 3 deletions.
58 changes: 55 additions & 3 deletions src/Hypered/Html/Struct/Prototypes/Motherboard/Documents.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
module Hypered.Html.Struct.Prototypes.Motherboard.Documents where

import qualified Data.Text as T
import Hypered.Html.Helpers
import Protolude hiding (div)
import Text.Blaze.Html5 (Html, (!))
Expand All @@ -9,11 +10,21 @@ import qualified Text.Blaze.Html5.Attributes as A
--------------------------------------------------------------------------------
data Document = Document
{ documentId :: Text
, documentUrl :: Text
, documentSource :: Text
, documentPublicationDate :: Text
, documentNumber :: Text
, documentPageNumber :: Int
, documentPDFOriginal :: Maybe Text
, documentCaseNumber :: Text
, documentStartDates :: [(Text, Text)]
, documentModifies :: [Text]
, documentLegislativeLinks :: [Text]
}

--------------------------------------------------------------------------------
prototypeMotherboardDocument :: Text -> Text -> Text -> Text -> Document -> Html
prototypeMotherboardDocument refliHomepage homepage justelUrl breadcrumb document@Document {..} = do
prototypeMotherboardDocument :: Text -> Text -> Text -> Document -> Html
prototypeMotherboardDocument refliHomepage homepage breadcrumb Document {..} = do
H.docType
H.html $ do -- TODO html(dir="ltr", lang="en")
H.head $ do
Expand All @@ -37,6 +48,47 @@ prototypeMotherboardDocument refliHomepage homepage justelUrl breadcrumb documen
div "u-container" $ do
H.p $
H.small ! A.class_ "breadcrumb" $ H.text breadcrumb
div "c-text flow-all limit-42em legislation" $ do
H.h1 ! A.class_ "mb-title" $ "15 JUILLET 2016. — Arrêté royal modifiant l'arrêté royal du 19 décembre 1967 portant règlement général en exécution de l'arrêté royal n° 38 du 27 juillet 1967 organisant le statut social des travailleurs indépendants"

H.div $
H.dl ! A.class_ "mb-pairs" $ do
H.dt "ELI"
H.dd $
H.a ! A.href (H.toValue documentUrl) $ "Justel"
H.dt "Source"
H.dd $ H.text documentSource
H.dt "Publication"
H.dd $ H.text documentPublicationDate
H.dt "Numéro"
H.dd $ H.text documentNumber
H.dt "Page"
H.dd $ H.text $ show documentPageNumber
H.dt "PDF"
H.dd $
maybe
"verion originale"
(\lnk -> H.a ! A.href (H.toValue $
"https://www.ejustice.just.fgov.be" <> lnk) $
"version originale")
documentPDFOriginal
H.dt "Dossier numéro"
H.dd $ H.text documentCaseNumber
H.dt "Entrée en vigueur / Effet"
H.dd $
mapM_ (\(a, b) -> H.text a >> H.text b) documentStartDates
H.dt "Texte modifié"
H.dd $
mapM_ (\a -> H.text a) documentModifies
H.dt "belgiquelex"
H.dd $ do
let f lnk =
if "http://reflex.raadvst-consetat.be" `T.isPrefixOf` lnk
then "Conseil d'Etat"
else "TODO"
mapM_
(\lnk -> H.a ! A.href (H.toValue lnk) $ H.text (f lnk))
documentLegislativeLinks

H.footer $
div "u-container" $ do
Expand All @@ -50,7 +102,7 @@ prototypeMotherboardDocument refliHomepage homepage justelUrl breadcrumb documen
H.p $
H.small $ do
"View the "
H.a ! A.href (H.toValue $ justelUrl) $ "original page"
H.a ! A.href (H.toValue $ documentUrl) $ "original page"
" on the Belgian Official Journal."
H.p $
H.small $ do
Expand Down

0 comments on commit 8ee4bf8

Please sign in to comment.