purs flycheck cleaning

This commit is contained in:
Jon Schoning 2021-08-27 21:41:17 -05:00 committed by Yann Esposito (Yogsototh)
parent 792be73f72
commit 07fcbb46ad
Signed by untrusted user who does not match committer: yogsototh
GPG key ID: 7B19A4C650D59646
14 changed files with 16 additions and 24 deletions

View file

@ -4,11 +4,10 @@ import Prelude hiding (div)
import App (editAccountSettings)
import Data.Lens (Lens', lens, use, (%=))
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Globals (app')
import Halogen as H
import Halogen.HTML (HTML, div, input, text)
import Halogen.HTML (div, input, text)
import Halogen.HTML.Elements (label)
import Halogen.HTML.Events (onChecked)
import Halogen.HTML.Properties (InputType(..), checked, for, id_, name, type_)
@ -84,6 +83,6 @@ usetting u' =
us <- use _us
void $ H.liftAff (editAccountSettings us)
handleAction (USubmit e) = do
handleAction (USubmit _) = do
us <- use _us
void $ H.liftAff (editAccountSettings us)

View file

@ -4,19 +4,16 @@ module Component.Add where
import Prelude hiding (div)
import App (destroy, editBookmark, lookupTitle)
import Data.Array (drop, foldMap)
import Data.Lens (Lens', lens, use, (%=), (.=))
import Data.Maybe (Maybe(..), maybe)
import Data.Monoid (guard)
import Data.String (null)
import Data.String (split) as S
import Data.String.Pattern (Pattern(..))
import Data.Tuple (fst, snd)
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import Globals (app', closeWindow, mmoment8601)
import Halogen as H
import Halogen.HTML (HTML, br_, button, div, form, input, label, p, span, table, tbody_, td, td_, text, textarea, tr_)
import Halogen.HTML (button, div, form, input, label, p, span, table, tbody_, td, td_, text, textarea, tr_)
import Halogen.HTML.Events (onSubmit, onValueChange, onChecked, onClick)
import Halogen.HTML.Properties (ButtonType(..), InputType(..), autocomplete, autofocus, checked, disabled, for, id_, name, required, rows, title, type_, value)
import Model (Bookmark)
@ -150,10 +147,10 @@ addbmark b' =
editField :: forall a. (a -> EditField) -> a -> BAction
editField f = BEditField <<< f
mmoment = mmoment8601 bm.time
toTextarea =
drop 1
<<< foldMap (\x -> [br_, text x])
<<< S.split (Pattern "\n")
-- toTextarea =
-- drop 1
-- <<< foldMap (\x -> [br_, text x])
-- <<< S.split (Pattern "\n")
handleAction :: BAction -> H.HalogenM BState BAction () o Aff Unit
handleAction (BDeleteAsk e) = do

View file

@ -6,7 +6,6 @@ import Component.BMark (BMessage(..), BSlot, bmark)
import Model (Bookmark, BookmarkId)
import Data.Array (filter)
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Halogen as H
import Halogen.HTML as HH

View file

@ -15,7 +15,7 @@ import Type.Proxy (Proxy(..))
import Effect.Aff (Aff)
import Globals (app', setFocus, toLocaleDateString)
import Halogen as H
import Halogen.HTML (HTML, a, br_, button, div, div_, form, input, label, span, text, textarea)
import Halogen.HTML (a, br_, button, div, div_, form, input, label, span, text, textarea)
import Halogen.HTML as HH
import Halogen.HTML.Events (onSubmit, onValueChange, onChecked, onClick)
import Halogen.HTML.Properties (ButtonType(..), InputType(..), autocomplete, checked, disabled, for, href, id_, name, required, rows, target, title, type_, value)

View file

@ -5,7 +5,6 @@ import Data.Const (Const)
import Effect.Aff (Aff)
import Foreign.Marked (marked)
import Halogen as H
import Halogen.HTML as HH
import Prelude (Void)
type Slot = H.Slot (Const Void) Void

View file

@ -45,7 +45,7 @@ nlist st' =
}
render :: NLState -> H.ComponentHTML NLAction () Aff
render st@{ notes } =
render { notes } =
HH.div_ (map renderNote notes)
where
renderNote note =

View file

@ -7,7 +7,7 @@ import Component.Markdown as Markdown
import Data.Array (drop, foldMap)
import Data.Foldable (for_)
import Data.Lens (Lens', lens, use, (%=), (.=))
import Data.Maybe (Maybe(..), maybe)
import Data.Maybe (maybe)
import Data.Monoid (guard)
import Data.String (null)
import Data.String (null, split) as S

View file

@ -19,6 +19,7 @@ data Action i
= SetInnerHTML
| Receive (Input i)
type Input :: forall k. k -> k
type Input i = i
type State i =
@ -53,7 +54,7 @@ mkComponent toRawHTML =
mel <- H.getHTMLElementRef elRef
for_ mel \el -> do
{ inputval } <- H.get
H.liftAff $ forkAff $ makeAff \cb -> do
H.liftAff $ forkAff $ makeAff \_ -> do
liftEffect $ unsafeSetInnerHTML el (toRawHTML inputval)
mempty
pure unit

View file

@ -55,9 +55,9 @@ tagcloudcomponent m' =
}
render :: TState -> H.ComponentHTML TAction () Aff
render s@{ mode:TagCloudModeNone } =
render { mode:TagCloudModeNone } =
div [class_ "tag_cloud" ] []
render s@{ mode, tagcloud } =
render { mode, tagcloud } =
div [class_ "tag_cloud mv3" ]
[
div [class_ "tag_cloud_header mb2"] $

View file

@ -29,9 +29,6 @@ import Web.HTML.Location (search)
import Web.HTML.Window (document, location)
import JSURI (decodeURIComponent)
import Partial.Unsafe (unsafePartial)
import Data.Maybe (fromJust)
unsafeDecode :: String -> String
unsafeDecode str = unsafePartial $ fromJust $ decodeURIComponent str

File diff suppressed because one or more lines are too long

Binary file not shown.

File diff suppressed because one or more lines are too long

Binary file not shown.