HomeInterface, WIP.
This commit is contained in:
parent
8e83eb3b56
commit
e172a41f2d
@ -14,6 +14,7 @@ import App.WS as WS
|
||||
import App.AuthenticationDaemonAdminInterface as AAI
|
||||
import App.DomainListInterface as DomainListInterface
|
||||
import App.ZoneInterface as ZoneInterface
|
||||
import App.HomeInterface as HomeInterface
|
||||
import App.Messages.DNSManagerDaemon as DNSManager
|
||||
import Halogen as H
|
||||
import Halogen.HTML as HH
|
||||
@ -43,6 +44,7 @@ type State = { token :: Maybe String
|
||||
|
||||
type ChildSlots =
|
||||
( log :: Log.Slot Unit
|
||||
, ho :: HomeInterface.Slot Unit
|
||||
, ws_auth :: WS.Slot Unit
|
||||
, ws_dns :: WS.Slot Unit
|
||||
, af :: AF.Slot Unit
|
||||
@ -51,6 +53,7 @@ type ChildSlots =
|
||||
, zi :: ZoneInterface.Slot Unit
|
||||
)
|
||||
|
||||
_ho = Proxy :: Proxy "ho"
|
||||
_log = Proxy :: Proxy "log"
|
||||
_ws_auth = Proxy :: Proxy "ws_auth"
|
||||
_ws_dns = Proxy :: Proxy "ws_dns"
|
||||
@ -91,7 +94,7 @@ render state
|
||||
where
|
||||
|
||||
-- TODO
|
||||
render_home = render_nothing
|
||||
render_home = Bulma.box [ HH.slot_ _ho unit HomeInterface.component unit]
|
||||
|
||||
render_zone domain = Bulma.box [ HH.slot _zi unit ZoneInterface.component domain ZoneInterfaceEvent]
|
||||
|
||||
|
41
src/App/HomeInterface.purs
Normal file
41
src/App/HomeInterface.purs
Normal file
@ -0,0 +1,41 @@
|
||||
-- | `App.HomeInterface` presents the website and its features.
|
||||
module App.HomeInterface where
|
||||
|
||||
import Prelude (Unit, unit, bind, discard, pure, ($), (<<<), (<>), Void)
|
||||
|
||||
|
||||
import Data.ArrayBuffer.Types (ArrayBuffer)
|
||||
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 Bulma as Bulma
|
||||
|
||||
data Query a = Noop a
|
||||
type Output = Unit
|
||||
type Slot = H.Slot Query Output
|
||||
type Input = Unit
|
||||
type Action = Unit
|
||||
type State = Unit
|
||||
|
||||
component :: forall m. MonadAff m => H.Component Query Input Output m
|
||||
component =
|
||||
H.mkComponent
|
||||
{ initialState
|
||||
, render
|
||||
, eval: H.mkEval $ H.defaultEval { handleQuery: handleQuery }
|
||||
}
|
||||
|
||||
handleQuery = case _ of
|
||||
Noop a -> pure a
|
||||
|
||||
initialState :: Input -> State
|
||||
initialState _ = unit
|
||||
|
||||
render :: forall m. State -> H.ComponentHTML Action () m
|
||||
render _ = Bulma.section_small [ Bulma.p "Hello." ]
|
Loading…
Reference in New Issue
Block a user