Use (#) instead of ($) for multi-line function chaining.

beta
Philippe Pittoli 2024-02-09 05:23:07 +01:00
parent 42192fb9e9
commit 41b4511a94
3 changed files with 17 additions and 28 deletions

View File

@ -15,7 +15,6 @@
, "effect" , "effect"
, "either" , "either"
, "exceptions" , "exceptions"
, "foldable-traversable"
, "foreign" , "foreign"
, "generic-parser" , "generic-parser"
, "halogen" , "halogen"

View File

@ -195,15 +195,6 @@ render state
render_dnsmanager_WS :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad render_dnsmanager_WS :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
render_dnsmanager_WS = HH.slot _ws_dns unit WS.component "ws://127.0.0.1:8081" DNSManagerDaemonEvent render_dnsmanager_WS = HH.slot _ws_dns unit WS.component "ws://127.0.0.1:8081" DNSManagerDaemonEvent
--case state.token of
-- Just _ -> Bulma.box $
-- [ HH.slot _dli unit DomainListInterface.component unit DomainListComponentEvent
-- ]
-- Nothing -> render_nothing
render_nothing :: forall monad. MonadAff monad => H.ComponentHTML Action ChildSlots monad
render_nothing = HH.div_ []
handleAction :: forall o monad. MonadAff monad => Action -> H.HalogenM State Action ChildSlots o monad Unit handleAction :: forall o monad. MonadAff monad => Action -> H.HalogenM State Action ChildSlots o monad Unit
handleAction = case _ of handleAction = case _ of
Routing page -> do Routing page -> do

View File

@ -20,14 +20,14 @@ module App.ZoneInterface where
import Prelude (Unit, unit, void import Prelude (Unit, unit, void
, bind, pure , bind, pure
, comparing, discard, map, show , comparing, discard, map, show
, ($), (/=), (<<<), (<>), (==), (>)) , ($), (/=), (<<<), (<>), (==), (>), (#))
import Data.Array as A import Data.Array as A
import Data.Int (fromString) import Data.Int (fromString)
import Data.ArrayBuffer.Types (ArrayBuffer) import Data.ArrayBuffer.Types (ArrayBuffer)
import Data.Array.NonEmpty as NonEmpty import Data.Array.NonEmpty as NonEmpty
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Foldable as Foldable -- import Data.Foldable as Foldable
import Data.Maybe (Maybe(..), fromMaybe, maybe) import Data.Maybe (Maybe(..), fromMaybe, maybe)
import Effect.Aff.Class (class MonadAff) import Effect.Aff.Class (class MonadAff)
import Halogen as H import Halogen as H
@ -259,10 +259,11 @@ render state
] ]
where where
sorted :: forall l. Array (SortableRecord (l)) -> Array (SortableRecord (l)) sorted :: forall l. Array (SortableRecord (l)) -> Array (SortableRecord (l))
sorted array = Foldable.foldl (<>) [] sorted array =
$ map (A.sortBy (comparing (_.rrid))) A.groupAllBy (comparing (_.rrtype)) array -- [x2 z2 x1 y z1 z3] -> [ NE[x2x1] NE[y] NE[z2z1z3] ]
$ map NonEmpty.toArray # map NonEmpty.toArray -- -> [[x2x1][y][z2z1z3]]
$ A.groupAllBy (comparing (_.rrtype)) array # map (A.sortBy (comparing (_.rrid))) -- -> [[x1x2][y][z1z2z3]]
# A.concat -- -> [x1 x2 y z1 z2 z3]
modal_rr_delete :: forall w. Int -> HH.HTML w Action modal_rr_delete :: forall w. Int -> HH.HTML w Action
modal_rr_delete rr_id = modal_rr_delete rr_id =
@ -727,22 +728,20 @@ render_resources records
render_mx_records = table_content all_mx_rr render_mx_records = table_content all_mx_rr
render_srv_records = table_content all_srv_rr render_srv_records = table_content all_srv_rr
table_content_with_separations records_ = HH.tbody_ $ split_records table_content_with_separations records_ = HH.tbody_ $
where A.groupAllBy (comparing (_.rrtype)) records_ -- [x x y y z] -> [NE[xx], NE[yy], NE[z]]
split_records = A.concat -- [[hh],[line],[hh],[line],[h]] -> [h h line h h line h] # map NonEmpty.toArray -- -> [[xx], [yy], [z]]
$ map A.concat -- [[hh],[line],[hh],[line],[h]] -> [h h line h h line h] # map (map rows) -- -> [[hh], [hh], [h]] ('h' means 'html')
$ A.intersperse [emptyline] -- [[hh], [hh], [h]] -> [[hh],[line],[hh],[line],[h]] # A.intersperse [emptyline] -- -> [[hh],[line],[hh],[line],[h]]
$ map (map rows) -- [[xx], [yy], [z]] -> [[hh], [hh], [h]] ('h' means 'html') # A.concat -- -> [h h line h h line h]
$ map NonEmpty.toArray -- [NE[xx], NE[yy], NE[z]] -> [[xx], [yy], [z]]
$ A.groupAllBy (comparing (_.rrtype)) records_ -- [x x y y z] -> [NE[xx], NE[yy], NE[z]]
emptyline = [ HH.tr_ [ Bulma.txt_name "", HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [] ] ] emptyline = HH.tr_ [ Bulma.txt_name "", HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [], HH.td_ [] ]
table_content records_ = HH.tbody_ $ A.concat $ map rows records_ table_content records_ = HH.tbody_ $ map rows records_
rows rr = [ HH.tr_ $ render_row rr ] -- <> error_row rr rows rr = HH.tr_ $ render_row rr -- <> error_row rr
render_row :: ResourceRecord -> Array (HH.HTML w Action) render_row :: ResourceRecord -> Array (HH.HTML w Action)
render_row rr = render_row rr =
case rr.rrtype of case rr.rrtype of
"SRV" -> "SRV" ->
[ Bulma.txt_name rr.rrtype [ Bulma.txt_name rr.rrtype