dnsmanager-webclient/src/App/Page/Home.purs

146 lines
5.4 KiB
Text

-- | `App.Page.Home` presents the website and its features.
module App.Page.Home where
import Prelude (Unit, pure, unit, ($))
-- import Data.Either (Either(..))
-- import Data.Maybe (Maybe(..), maybe)
-- import Data.Tuple (Tuple(..))
import Effect.Aff.Class (class MonadAff)
import Halogen as H
import Halogen.HTML as HH
-- import Halogen.HTML.Events as HE
import Halogen.HTML.Properties as HP
import CSSClasses as C
import Web as Web
type Input = Unit
type Action = Unit
type State = Unit
data Query a = DoNothing a
type Output = Unit
type Slot = H.Slot Query Output
component :: forall m. MonadAff m => H.Component Query Input Output m
component =
H.mkComponent
{ initialState
, render
, eval: H.mkEval $ H.defaultEval
{ handleAction = handleAction
}
}
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
handleAction _ = pure unit
initialState :: forall input. input -> State
initialState _ = unit
render :: forall m. State -> H.ComponentHTML Action () m
render _ = HH.div_
[ Web.hero_danger
[ HH.text "Read the news! 📰" ]
[ Web.hr
, Web.p "Check out the News page regarding the events of the last few days on netlibre."
]
, Web.section_small
[ Web.h1 "Welcome to netlib.re"
, Web.subtitle "Free domain names for the common folks"
, Web.hr
, render_description
, render_update_why_and_contact
, Web.hr
, render_how_and_code
]
]
where
title = Web.h4
b x = Web.column_ [ Web.box x ]
render_description = Web.columns_ [ render_basics, render_no_expert, render_no_housing ]
render_update_why_and_contact = Web.columns_ [ render_updates, render_why, render_contact ]
render_basics
= b [ title "What is provided?"
, Web.p "Reserve a domain name in <something>.netlib.re for free."
, Web.p "Manage your own DNS zone."
]
render_no_expert
= b [ title "No need to be an expert"
, Web.p """
This website will help you through your configuration, as much as we can.
"""
]
render_no_housing
= b [ title "No housing, just a name"
, Web.p """
We don't host your services or websites.
We just provide a name.
You can host your websites anywhere you want: at home for example.
"""
]
render_updates
= b [ title "Automatic updates"
, Web.p "Update your records with a single, stupidly simple command. For example:"
, Web.quote [ Web.strong "wget https://www.netlib.re/token-update/<token>" ]
, Web.p "Every A and AAAA records have tokens for easy updates."
]
render_why
= b [ title "Why?"
, Web.p "Because everyone should be able to have a place on the Internet."
, Web.p "We provide a name, build something meaningful with it."
]
render_contact
= b [ title "Contact"
, Web.p "You have a question, you have seen a bug, you have suggestions or you just want to chat?"
, Web.p "You can contact me: philippe@netlib.re"
, Web.p "For legal matter: abuse@netlib.re"
]
render_how_and_code = Web.columns_ [ render_how, render_code ]
render_how
= b [ title "How does this work?"
, Web.p "We pay for the domain names (netlib.re and codelib.re) and let you have a subdomain."
, Web.p "This service helps you manage your domain (a subdomain of netlib.re or codelib.re)."
]
render_code
= b [ title "I want to see the code! 🤓​"
, Web.p "The project is fully open-source (ISC licence)."
, HH.text "There are a few parts:"
, HH.ul_
[ link "https://git.baguette.netlib.re/Baguette/authd" "authentication daemon"
"""
to authenticate clients through different services;
"""
, link "https://git.baguette.netlib.re/Baguette/dnsmanager" "dnsmanager daemon"
"""
an interactive database enabling clients to ask for domains then to manage DNS zones;
"""
, link "https://git.baguette.netlib.re/Baguette/dnsmanager-webclient"
"dnsmanager webclient"
"""
this user-friendly website, so you can manage your zones. 🥰
"""
]
, Web.hr
, Web.p "But of course, there are a few more technical parts:"
, HH.ul_
[ link "https://git.baguette.netlib.re/Baguette/libipc" "libIPC"
"""
the Inter Process Communication library used between different applications,
such as authd and dnsmanagerd;
"""
, link "https://git.baguette.netlib.re/Baguette/dodb.cr" "dodb"
"""
the Document Oriented DataBase, enabling to store serialized objects
(a Zone, a User, etc.) in simple files as opposed to the usual complexity of
traditional databases.
"""
]
]
link url link_title content
= HH.li_ [ Web.outside_link [] url link_title, HH.text ", ", HH.text content ]