Created
April 26, 2016 14:51
-
-
Save natefaubion/18ce4523d9d38698ee89afcb130a17a0 to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import Prelude | |
import Control.Monad.Eff (Eff) | |
import Data.List (List(..), (:)) | |
import Data.Maybe (Maybe(..)) | |
import Halogen (ParentState, parentState, ParentQuery, Component, parentComponent, ParentHTML, Natural, ParentDSL, HalogenEffects, runUI) | |
import Halogen.HTML as H | |
import Halogen.Util (runHalogenAff, awaitBody) | |
import Unsafe.Coerce (unsafeCoerce) | |
foreign import data Private :: * | |
foreign import data PrivateF :: * -> * | |
type OpaqueState s f g = ParentState s Private f PrivateF g Private | |
type OpaqueQuery f = ParentQuery f PrivateF Private | |
opaque | |
:: forall s s' f f' g p | |
. Component (ParentState s s' f f' g p) (ParentQuery f f' p) g | |
-> Component (OpaqueState s f g) (OpaqueQuery f) g | |
opaque = unsafeCoerce | |
type FooState = List String | |
type FooStateP g = OpaqueState FooState FooQuery g | |
data FooQuery a = Set FooState a | |
type FooQueryP = OpaqueQuery FooQuery | |
foo | |
:: forall g | |
. Functor g | |
=> Component (FooStateP g) FooQueryP g | |
foo = opaque $ parentComponent { render, eval, peek: Nothing } where | |
render :: FooState -> ParentHTML (FooStateP g) FooQuery FooQueryP g Unit | |
render (Cons x xs) = | |
H.div_ | |
[ H.text x | |
, H.slot unit \_ -> { component: foo, initialState: parentState xs } | |
] | |
render Nil = | |
H.text "" | |
eval :: Natural FooQuery (ParentDSL FooState (FooStateP g) FooQuery FooQueryP g Unit) | |
eval (Set list next) = pure next -- TBD | |
main :: Eff (HalogenEffects ()) Unit | |
main = runHalogenAff do | |
body <- awaitBody | |
runUI foo (parentState $ "a" : "b" : "c" : "d" : Nil) body |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment