HomeInterface: module can be compiled, nothing to render yet.

beta
Philippe Pittoli 2023-07-15 13:56:32 +02:00
parent e172a41f2d
commit eb780fc5ce
1 changed files with 16 additions and 16 deletions

View File

@ -1,25 +1,23 @@
-- | `App.HomeInterface` presents the website and its features.
module App.HomeInterface where
import Prelude (Unit, unit, bind, discard, pure, ($), (<<<), (<>), Void)
import Prelude (Unit, pure, unit, ($))
import Data.ArrayBuffer.Types (ArrayBuffer)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..))
-- 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 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
data Query a = DoNothing a
type Slot = H.Slot Query Unit
type Input = Unit
type Output = Unit
type Action = Unit
type State = Unit
@ -28,13 +26,15 @@ component =
H.mkComponent
{ initialState
, render
, eval: H.mkEval $ H.defaultEval { handleQuery: handleQuery }
, eval: H.mkEval $ H.defaultEval
{ handleAction = handleAction
}
}
handleQuery = case _ of
Noop a -> pure a
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
handleAction _ = pure unit
initialState :: Input -> State
initialState :: forall input. input -> State
initialState _ = unit
render :: forall m. State -> H.ComponentHTML Action () m