1
Fork 0

Remove extra whitespace in examples files

This commit is contained in:
Jordan Martinez 2019-05-18 20:31:32 -07:00
commit f94de112b5
5 changed files with 47 additions and 52 deletions

View file

@ -18,7 +18,7 @@ type Slot =
type State =
( items :: Array String
, selection :: Maybe String
, selection :: Maybe String
, buttonLabel :: String
)
@ -32,7 +32,7 @@ type Input =
, buttonLabel :: String
}
input :: Input -> S.Input State
input :: Input -> S.Input State
input { items, buttonLabel } =
{ inputType: S.Toggle
, search: Nothing
@ -54,8 +54,8 @@ spec = S.defaultSpec { render = render, handleMessage = handleMessage }
H.raise $ SelectionChanged st.selection selection
_ -> pure unit
render st =
HH.div
render st =
HH.div
[ class_ "Dropdown" ]
[ renderToggle, renderContainer ]
where
@ -70,13 +70,12 @@ spec = S.defaultSpec { render = render, handleMessage = handleMessage }
( renderItem `mapWithIndex` st.items )
where
renderItem index item =
HH.div
( SS.setItemProps index
[ classes_
HH.div
( SS.setItemProps index
[ classes_
[ "Dropdown__item"
, "Dropdown__item--highlighted" # guard (st.highlightedIndex == Just index)
]
]
)
)
[ HH.text item ]

View file

@ -24,11 +24,11 @@ import Internal.RemoteData as RD
import Select as S
import Select.Setters as SS
type Slot =
type Slot =
S.Slot Query ChildSlots Message
type State =
( selections :: Array Location
( selections :: Array Location
, available :: RD.RemoteData String (Array Location)
)
@ -39,17 +39,17 @@ data Action
data Query a
= GetSelections (Array Location -> a)
data Message
= ItemRemoved Location
data Message
= ItemRemoved Location
| SelectionsChanged (Array Location)
type ChildSlots =
type ChildSlots =
( dropdown :: D.Slot Unit )
-- this typeahead will be opaque; users can just use this pre-built
-- input instead of the usual select one.
input :: S.Input State
input =
input =
{ inputType: S.Text
, debounceTime: Just (Milliseconds 300.0)
, search: Nothing
@ -59,15 +59,15 @@ input =
}
spec :: S.Spec State Query Action ChildSlots Message Aff
spec = S.defaultSpec
spec = S.defaultSpec
{ render = render
, handleAction = handleAction
, handleQuery = handleQuery
, handleMessage = handleMessage
}
where
handleMessage
:: S.Message
handleMessage
:: S.Message
-> H.HalogenM (S.State State) (S.Action Action) ChildSlots Message Aff Unit
handleMessage = case _ of
S.Selected ix -> do
@ -75,7 +75,7 @@ spec = S.defaultSpec
for_ st.available \arr ->
for_ (arr !! ix) \item -> do
let newSelections = item : st.selections
H.modify_ _
H.modify_ _
{ selections = item : st.selections
, available = RD.Success (filter (_ /= item) arr)
, search = ""
@ -83,7 +83,7 @@ spec = S.defaultSpec
H.raise $ SelectionsChanged newSelections
S.Searched str -> do
st <- H.get
-- we'll use an external api to search locations
-- we'll use an external api to search locations
H.modify_ _ { available = RD.Loading }
items <- H.liftAff $ searchLocations str
H.modify_ _ { available = items <#> \xs -> difference xs st.selections }
@ -92,13 +92,13 @@ spec = S.defaultSpec
-- You can remove all type signatures except for this one; we need to tell the
-- compiler about the `a` type variable. The minimal necessary signature is below.
handleQuery :: forall a. Query a -> H.HalogenM _ _ _ _ _ (Maybe a)
handleQuery = case _ of
handleQuery = case _ of
GetSelections reply -> do
st <- H.get
pure $ Just $ reply st.selections
handleAction
:: Action
handleAction
:: Action
-> H.HalogenM (S.State State) (S.Action Action) ChildSlots Message Aff Unit
handleAction = case _ of
Remove item -> do
@ -109,23 +109,23 @@ spec = S.defaultSpec
HandleDropdown msg -> case msg of
D.SelectionChanged oldSelection newSelection -> do
st <- H.get
let
let
mkLocation str = { name: "User Added: " <> str, population: "1" }
newSelections = case oldSelection, newSelection of
Nothing, Nothing ->
Nothing, Nothing ->
Nothing
Nothing, Just str ->
Nothing, Just str ->
Just (mkLocation str : st.selections)
Just str, Nothing ->
Just str, Nothing ->
Just (filter (_ /= mkLocation str) st.selections)
Just old, Just new ->
Just old, Just new ->
Just (mkLocation new : (filter (_ /= mkLocation old) st.selections))
for_ newSelections \selections ->
for_ newSelections \selections ->
H.modify_ _ { selections = selections }
render :: S.State State -> H.ComponentHTML (S.Action Action) ChildSlots Aff
render st =
HH.div
render st =
HH.div
[ class_ "Typeahead" ]
[ renderSelections, renderInput, renderDropdown, renderContainer ]
where
@ -139,7 +139,7 @@ spec = S.defaultSpec
renderSelectedItem item =
HH.div
[ class_ "Typeahead__item--selected Location" ]
[ HH.span
[ HH.span
[ class_ "Location__name" ]
[ HH.text item.name ]
, closeButton item
@ -147,18 +147,18 @@ spec = S.defaultSpec
closeButton item =
HH.span
[ class_ "Location__closeButton"
[ class_ "Location__closeButton"
, HE.onClick \_ -> Just $ S.Action $ Remove item
]
[ HH.text "×" ]
renderInput = HH.input $ SS.setInputProps
[ classes_
[ classes_
[ "Typeahead__input"
, "Typeahead__input--selections" # guard hasSelections
, "Typeahead__input--active" # guard (st.visibility == S.On)
]
, HP.placeholder "Type to search..."
, HP.placeholder "Type to search..."
]
renderDropdown = whenElem (st.visibility == S.On) \_ ->
@ -169,10 +169,10 @@ spec = S.defaultSpec
dropdownInput = { items: [ "Earth", "Mars" ], buttonLabel: "Human Planets" }
renderContainer = whenElem (st.visibility == S.On) \_ ->
HH.div
(SS.setContainerProps
[ classes_
[ "Typeahead__container"
HH.div
(SS.setContainerProps
[ classes_
[ "Typeahead__container"
, "Typeahead__container--hasItems" # guard hasItems
]
]
@ -186,14 +186,14 @@ spec = S.defaultSpec
RD.NotAsked -> renderMsg "No search performed..."
RD.Loading -> renderMsg "Loading..."
RD.Failure e -> renderMsg e
RD.Success available
RD.Success available
| hasItems -> renderItem `mapWithIndex` available
| otherwise -> renderMsg "No results found"
renderItem index { name, population } =
HH.div
(SS.setItemProps index [ classes_ [ base, highlight, "Location" ] ])
[ HH.span
HH.div
(SS.setItemProps index [ classes_ [ base, highlight, "Location" ] ])
[ HH.span
[ class_ "Location__name" ]
[ HH.text name ]
, HH.span
@ -214,7 +214,6 @@ type Location =
searchLocations :: String -> Aff (RD.RemoteData String (Array Location))
searchLocations search = do
res <- AX.get AR.json ("https://swapi.co/api/planets/?search=" <> search)
res <- AX.get AR.json ("https://swapi.co/api/planets/?search=" <> search)
let body = lmap AR.printResponseFormatError res.body
pure $ RD.fromEither $ traverse decodeJson =<< (_ .: "results") =<< decodeJson =<< body

View file

@ -13,4 +13,3 @@ classes_ = HP.classes <<< map HH.ClassName
whenElem :: forall p i. Boolean -> (Unit -> HH.HTML i p) -> HH.HTML i p
whenElem cond render = if cond then render unit else HH.text ""

View file

@ -1,4 +1,4 @@
-- | Copied over from
-- | Copied over from
-- | https://github.com/krisajenkins/purescript-remotedata
-- |
-- | due to dependency conflicts
@ -42,4 +42,3 @@ fromMaybe (Just value) = Success value
fromEither :: forall e a. Either e a -> RemoteData e a
fromEither (Left err) = Failure err
fromEither (Right value) = Success value

View file

@ -48,7 +48,7 @@ type Components
routes :: Components
routes = M.fromFoldable
[ Tuple "typeahead" $ proxy typeahead
, Tuple "dropdown" $ proxy dropdown
, Tuple "dropdown" $ proxy dropdown
]
app :: H.Component HH.HTML (Const Void) String Void Aff
@ -74,9 +74,9 @@ selectElements
:: { query :: QuerySelector, attr :: String }
-> Aff (Array { element :: HTMLElement, attr :: String })
selectElements { query, attr } = do
nodeArray <- liftEffect do
nodeArray <- liftEffect do
toArray =<< querySelectorAll query <<< toParentNode =<< document =<< window
let
let
elems = fromMaybe [] <<< sequence $ fromNode <$> nodeArray
attrs <- liftEffect $ traverse (getAttribute attr <<< toElement) elems
pure $ zipWith ({ element: _, attr: _ }) elems (fromMaybe "" <$> attrs)
@ -104,4 +104,3 @@ typeahead = H.mkComponent
}
where
label = SProxy :: SProxy "typeahead"