Skip to content

Commit

Permalink
Cleanup
Browse files Browse the repository at this point in the history
  • Loading branch information
qwbarch committed Jul 16, 2023
1 parent f74fb5a commit 3315863
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 10 deletions.
10 changes: 4 additions & 6 deletions example/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -38,12 +38,10 @@ component =
mkComponent
{ initialState: const unit
, render
, eval:
mkEval $
defaultEval
{ handleAction = handleAction
, initialize = Just Initialize
}
, eval: mkEval defaultEval
{ handleAction = handleAction
, initialize = Just Initialize
}
}
where
handleAction = case _ of
Expand Down
8 changes: 4 additions & 4 deletions src/Halogen/Typewriter.purs
Original file line number Diff line number Diff line change
Expand Up @@ -3,10 +3,9 @@ module Halogen.Typewriter where
import Prelude hiding (div)

import CSS (opacity)
import Control.Monad.Rec.Class (forever)
import Control.Monad.State (get)
import Data.Foldable (foldMap)
import Data.Lens (view, (%=), (.=))
import Data.Lens (view, (%=), (.=), (<>=))
import Data.List.Lazy (List, head, tail)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Newtype (unwrap)
Expand Down Expand Up @@ -124,7 +123,7 @@ typewriter = mkComponent { initialState, render, eval }
, jitter: input.jitter
, running: true
}
eval = mkEval (defaultEval { handleAction = handleAction, initialize = Just Initialize })
eval = mkEval defaultEval { handleAction = handleAction, initialize = Just Initialize }

-- The defined class names do nothing by default.
-- These are for the user's convenience, if they want to change styles for the respective classes.
Expand Down Expand Up @@ -162,6 +161,7 @@ typewriter = mkComponent { initialState, render, eval }
case head state.words of
Nothing -> do
running .= false
cursorHidden .= true
raise Finished
Just word -> do
case state.mode of
Expand All @@ -177,7 +177,7 @@ typewriter = mkComponent { initialState, render, eval }
coefficient <- liftEffect $ state.jitter
sleep (_ * coefficient) typeDelay
-- Add the next letter to outputText.
outputText %= (_ <> singleton letter)
outputText <>= singleton letter
Deleting ->
-- When outputText is empty, start typing.
if null state.outputText then mode .= Typing
Expand Down

0 comments on commit 3315863

Please sign in to comment.